Archived
1
0
Fork 0

Added plugin loading, and the most basic hook capability.

This commit is contained in:
Julien Dessaux 2011-05-01 03:11:32 +02:00
parent 7e89b50bfe
commit c497b24700
6 changed files with 68 additions and 35 deletions

View file

@ -19,6 +19,7 @@ import Prelude hiding (catch)
import System.IO import System.IO
import System.Log.Logger import System.Log.Logger
import Hsbot.Plugin
import Hsbot.Types import Hsbot.Types
import Hsbot.Utils import Hsbot.Utils
@ -77,7 +78,7 @@ runHsbot = do
chan <- lift $ asks envChan chan <- lift $ asks envChan
(liftIO . forkIO $ botReader connhdl tlsCtx chan myOwnThreadId) >>= lift . addThreadIdToQuitMVar (liftIO . forkIO $ botReader connhdl tlsCtx chan myOwnThreadId) >>= lift . addThreadIdToQuitMVar
-- Then we spawn all plugins -- Then we spawn all plugins
-- asks envSocket >>= mapM_ ( ----- what's next? the core server handling! ----- ) (lift $ asks envConfig) >>= mapM_ loadPlugin . configPlugins
-- Finally we spawn the main bot loop -- Finally we spawn the main bot loop
bot <- get bot <- get
finalStateMVar <- liftIO newEmptyMVar finalStateMVar <- liftIO newEmptyMVar
@ -86,6 +87,7 @@ runHsbot = do
code <- asks envQuitMv >>= liftIO . takeMVar code <- asks envQuitMv >>= liftIO . takeMVar
-- and we clean things up -- and we clean things up
asks envThreadIdsMv >>= liftIO . readMVar >>= liftIO . mapM_ killThread asks envThreadIdsMv >>= liftIO . readMVar >>= liftIO . mapM_ killThread
-- TODO : kill plugin threads
return code return code
storeFinalState :: MVar BotState -> BotState -> Env IO () storeFinalState :: MVar BotState -> BotState -> Env IO ()
storeFinalState finalStateMVar finalState = liftIO $ putMVar finalStateMVar finalState storeFinalState finalStateMVar finalState = liftIO $ putMVar finalStateMVar finalState
@ -103,8 +105,16 @@ botReader handle Nothing chan fatherThreadId = forever $
killThread myId killThread myId
return "" return ""
handleIncomingStr :: Chan Message -> String -> IO ()
handleIncomingStr chan str = do
case IRC.decode str of
Just msg -> do
debugM "Ircd.Reader" $ "<-- " ++ (show msg)
writeChan chan $ IncomingMsg msg
Nothing -> debugM "Ircd.Reader" $ "Error: couldn't decode : " ++ str -- TODO: spam control
botLoop :: Bot (Env IO) () botLoop :: Bot (Env IO) ()
botLoop = do botLoop = forever $ do
chan <- lift $ asks envChan chan <- lift $ asks envChan
hooks <- gets botHooks hooks <- gets botHooks
msg <- liftIO $ readChan chan msg <- liftIO $ readChan chan
@ -115,16 +125,9 @@ botLoop = do
env <- lift ask env <- lift ask
let connhdl = envHandle env let connhdl = envHandle env
tlsCtx = envTLSCtx env tlsCtx = envTLSCtx env
liftIO $ debugM "Ircd.Reader" $ "--> " ++ (show outMsg)
liftIO . sendStr connhdl tlsCtx $ IRC.encode outMsg liftIO . sendStr connhdl tlsCtx $ IRC.encode outMsg
handleIncomingStr :: Chan Message -> String -> IO ()
handleIncomingStr chan str = do
case IRC.decode str of
Just msg -> do
debugM "Ircd.Reader" $ "<-- " ++ (show msg)
writeChan chan $ IncomingMsg msg
Nothing -> debugM "Ircd.Reader" $ "Error: couldn't decode : " ++ str -- TODO: spam control
terminateHsbot :: Env IO () terminateHsbot :: Env IO ()
terminateHsbot = do terminateHsbot = do
liftIO $ infoM "Hsbot.Core" "Closing connection" liftIO $ infoM "Hsbot.Core" "Closing connection"

View file

@ -11,13 +11,13 @@ import qualified Network.IRC as IRC
import Hsbot.Types import Hsbot.Types
-- Plugin Utils -- Plugin Utils
readMsg :: Plugin IO (Message) readMsg :: Plugin (Env IO) (Message)
readMsg = gets pluginChan >>= liftIO . readChan >>= return readMsg = gets pluginChan >>= liftIO . readChan >>= return
writeMsg :: Message -> Plugin IO () writeMsg :: Message -> Plugin (Env IO) ()
writeMsg msg = gets pluginMaster >>= liftIO . flip writeChan msg writeMsg msg = gets pluginMaster >>= liftIO . flip writeChan msg
answerMsg :: IRC.Message -> String -> Plugin IO () answerMsg :: IRC.Message -> String -> Plugin (Env IO) ()
answerMsg request msg = answerMsg request msg =
case IRC.msg_params request of case IRC.msg_params request of
sender:_ -> writeMsg . OutgoingMsg $ IRC.Message Nothing "PRIVMSG" [sender, msg] sender:_ -> writeMsg . OutgoingMsg $ IRC.Message Nothing "PRIVMSG" [sender, msg]

38
Hsbot/Plugin.hs Normal file
View file

@ -0,0 +1,38 @@
module Hsbot.Plugin
( loadPlugin
) where
import Control.Concurrent
import qualified Data.Map as M
import Control.Monad.Reader
import Control.Monad.State
import System.Log.Logger
import Hsbot.Types
loadPlugin :: PluginId -> Bot (Env IO) ()
loadPlugin pId = do
bot <- get
chan <- liftIO (newChan :: IO (Chan Message))
master <- lift $ asks envChan
let name = pluginName pId
loop = pluginEp pId
oldPlugins = botPlugins bot
pState = PluginState { pluginId = pId
, pluginChan = chan
, pluginMaster = master }
-- We check for unicity
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
put $ bot { botPlugins = newPlugins
, botHooks = chan : botHooks bot }
where
storeFinalState :: MVar PluginState -> PluginState -> Env IO ()
storeFinalState finalStateMVar finalState = liftIO $ putMVar finalStateMVar finalState

View file

@ -1,35 +1,28 @@
module Hsbot.Plugin.Ping module Hsbot.Plugin.Ping
( pingId ( ping
, ping , thePing
) where ) where
import Control.Concurrent.Chan () import Control.Concurrent.Chan ()
import Control.Exception import Control.Monad.State
import Control.Monad.State (execStateT, forever)
import qualified Network.IRC as IRC import qualified Network.IRC as IRC
import Prelude hiding (catch) import Prelude hiding (catch)
import Hsbot.Message import Hsbot.Message
import Hsbot.Types import Hsbot.Types
pingId :: PluginId ping :: PluginId
pingId = PluginId ping = PluginId
{ pluginName = "ping" { pluginName = "ping"
, pluginEp = ping } , pluginEp = thePing }
-- | The plugin's main entry point
ping :: PluginState -> IO ()
ping state = do
_ <- (execStateT run state) `catch` (\(_ :: AsyncException) -> return state)
return ()
-- | The IrcPlugin monad main function -- | The IrcPlugin monad main function
run :: Plugin IO () thePing :: Plugin (Env IO) ()
run = forever $ do thePing = forever $ do
msg <- readMsg msg <- readMsg
eval msg eval msg
where where
eval :: Message -> Plugin IO () eval :: Message -> Plugin (Env IO) ()
eval (IncomingMsg msg) eval (IncomingMsg msg)
| (IRC.msg_command msg) == "PING" = writeMsg . OutgoingMsg . IRC.Message Nothing "PONG" $ IRC.msg_params msg | (IRC.msg_command msg) == "PING" = writeMsg . OutgoingMsg . IRC.Message Nothing "PONG" $ IRC.msg_params msg
| otherwise = return () | otherwise = return ()

View file

@ -38,7 +38,7 @@ data BotEnv = BotEnv
type Bot = StateT BotState type Bot = StateT BotState
data BotState = BotState data BotState = BotState
{ botPlugins :: M.Map String (PluginState, MVar (), ThreadId) { botPlugins :: M.Map String (PluginState, MVar PluginState, ThreadId)
, botHooks :: [Chan Message] , botHooks :: [Chan Message]
, botChannels :: [String] , botChannels :: [String]
, botNickname :: String , botNickname :: String
@ -55,7 +55,7 @@ data PluginState = PluginState
data PluginId = PluginId data PluginId = PluginId
{ pluginName :: String { pluginName :: String
, pluginEp :: PluginState -> IO () , pluginEp :: Plugin (Env IO) ()
} }
-- Messaging -- Messaging
@ -73,7 +73,7 @@ data Config = Config
, configChannels :: [String] , configChannels :: [String]
, configNicknames :: [String] , configNicknames :: [String]
, configRealname :: String , configRealname :: String
, configPlugins :: [(String, Chan Message -> Chan Message -> IO ())] , configPlugins :: [PluginId]
} }
data TLSConfig = TLSConfig data TLSConfig = TLSConfig

View file

@ -1,5 +1,5 @@
Name: hsbot Name: hsbot
Version: 0.4.1 Version: 0.4.4
Cabal-version: >=1.2 Cabal-version: >=1.2
Synopsis: A multipurposes IRC bot Synopsis: A multipurposes IRC bot
Description: Description:
@ -19,11 +19,10 @@ Build-type: Simple
Library Library
ghc-options: -Wall ghc-options: -Wall
exposed-modules: Hsbot exposed-modules: Hsbot
--Hsbot.Command
Hsbot.Config Hsbot.Config
Hsbot.Core Hsbot.Core
Hsbot.Message Hsbot.Message
--Hsbot.Plugin Hsbot.Plugin
Hsbot.Plugin.Ping Hsbot.Plugin.Ping
Hsbot.Types Hsbot.Types
Hsbot.Utils Hsbot.Utils