Archived
1
0
Fork 0

Made the Plugin monad a Reader instead of a State since it can't change.

This commit is contained in:
Julien Dessaux 2011-05-06 19:15:40 +02:00
parent 4ec66d2ad7
commit a8c0c85787
7 changed files with 15 additions and 22 deletions

View file

@ -5,17 +5,17 @@ module Hsbot.Message
) where
import Control.Concurrent
import Control.Monad.State
import Control.Monad.Reader
import qualified Network.IRC as IRC
import Hsbot.Types
-- Plugin Utils
readMsg :: Plugin (Env IO) Message
readMsg = gets pluginChan >>= liftIO . readChan
readMsg = asks pluginChan >>= liftIO . readChan
writeMsg :: Message -> Plugin (Env IO) ()
writeMsg msg = gets pluginMaster >>= liftIO . flip writeChan msg
writeMsg msg = asks pluginMaster >>= liftIO . flip writeChan msg
answerMsg :: IRC.Message -> String -> Plugin (Env IO) ()
answerMsg request msg =

View file

@ -23,19 +23,16 @@ loadPlugin pId = do
let name = pluginName pId
loop = pluginEp pId
oldPlugins = botPlugins bot
pState = PluginState { pluginId = pId
, pluginChan = chan
, pluginMaster = master }
pEnv = PluginEnv { pluginId = pId
, pluginChan = chan
, pluginMaster = master }
case M.lookup name oldPlugins of
Just _ -> liftIO . warningM "Hsbot.Core.LoadPlugin" $ "Not loading already loaded plugin : " ++ name
Nothing -> do
liftIO . infoM "Hsbot.Core.LoadPlugin" $ "Loading plugin : " ++ name
env <- lift ask
finalStateMVar <- liftIO newEmptyMVar
threadId <- liftIO . forkIO $ runReaderT (execStateT loop pState >>= storeFinalState finalStateMVar) env
let newPlugins = M.insert name (pState, finalStateMVar, threadId) oldPlugins
threadId <- liftIO . forkIO $ runReaderT (runReaderT loop pEnv) env
let newPlugins = M.insert name (pEnv, threadId) oldPlugins
put $ bot { botPlugins = newPlugins
, botHooks = chan : botHooks bot }
storeFinalState :: MVar PluginState -> PluginState -> Env IO ()
storeFinalState finalStateMVar finalState = liftIO $ putMVar finalStateMVar finalState

View file

@ -6,7 +6,7 @@ module Hsbot.Plugin.Duck
import Control.Concurrent.Chan ()
import qualified Data.List as L
import Control.Monad.State
import Control.Monad.Reader
import qualified Network.IRC as IRC
import Prelude hiding (catch)

View file

@ -4,7 +4,7 @@ module Hsbot.Plugin.Ping
) where
import Control.Concurrent.Chan ()
import Control.Monad.State
import Control.Monad.Reader
import qualified Network.IRC as IRC
import Prelude hiding (catch)

View file

@ -7,8 +7,8 @@ module Hsbot.Types
, Env
, Message (..)
, Plugin
, PluginEnv (..)
, PluginId (..)
, PluginState (..)
, TLSConfig (..)
) where
@ -39,16 +39,16 @@ data BotEnv = BotEnv
type Bot = StateT BotState
data BotState = BotState
{ botPlugins :: M.Map String (PluginState, MVar PluginState, ThreadId)
{ botPlugins :: M.Map String (PluginEnv, ThreadId)
, botHooks :: [Chan Message]
, botChannels :: [String]
, botNickname :: String
}
-- The Plugin monad
type Plugin = StateT PluginState
type Plugin = ReaderT PluginEnv
data PluginState = PluginState
data PluginEnv = PluginEnv
{ pluginId :: PluginId
, pluginChan :: Chan Message
, pluginMaster :: Chan Message

View file

@ -1,7 +1,6 @@
module Hsbot.Utils
( addThreadIdToQuitMVar
, delThreadIdFromQuitMVar
, first
, initTLSEnv
, readCertificate
, readPrivateKey
@ -41,9 +40,6 @@ setGlobalQuitMVar status = do
quitMv <- asks envQuitMv
liftIO $ putMVar quitMv status
first :: (a, b, c) -> a
first (a, _, _) = a
-- Helpers
sendStr :: Handle -> Maybe TLSCtx -> String -> IO ()
sendStr _ (Just ctx) msg = sendData ctx $ L.fromChunks [C.pack msg]

View file

@ -1,5 +1,5 @@
Name: hsbot
Version: 0.4.8
Version: 0.4.9
Cabal-version: >=1.2
Synopsis: A multipurposes IRC bot
Description: