Archived
1
0
Fork 0

Implemented ircbot update messages.

This commit is contained in:
Julien Dessaux 2010-05-24 22:46:20 +02:00
parent 5b8cffbf68
commit a12e492772
6 changed files with 73 additions and 44 deletions

View file

@ -36,7 +36,7 @@ unregisterCommand cmd pluginName' = do
-- | Processes an internal command -- | Processes an internal command
processInternalCommand :: IrcBotMsg -> IrcBot () processInternalCommand :: IrcBotMsg -> IrcBot ()
processInternalCommand (IntIrcCmd ircCmd) processInternalCommand (IntIrcCmd ircCmd)
| ircCmdTo ircCmd == "CORE" = processCoreCommand ircCmd | ircCmdTo ircCmd == "CORE" = processCoreCommand ircCmd
| otherwise = do | otherwise = do
plugins <- gets ircBotPlugins plugins <- gets ircBotPlugins
case M.lookup (ircCmdTo ircCmd) plugins of case M.lookup (ircCmdTo ircCmd) plugins of
@ -52,8 +52,18 @@ processCoreCommand ircCmd = do
case command' of case command' of
"LIST" -> listPlugins originalRequest (ircCmdFrom ircCmd) "LIST" -> listPlugins originalRequest (ircCmdFrom ircCmd)
"LOAD" -> loadIrcPlugin $ ircCmdMsg ircCmd "LOAD" -> loadIrcPlugin $ ircCmdMsg ircCmd
"UNLOAD" -> unloadPlugin $ ircCmdMsg ircCmd "UNLOAD" -> unloadIrcPlugin $ ircCmdMsg ircCmd
"UPDATE" -> processUpdateCommand ircCmd
"REGISTER" -> registerCommand (ircCmdMsg ircCmd) (ircCmdFrom ircCmd) "REGISTER" -> registerCommand (ircCmdMsg ircCmd) (ircCmdFrom ircCmd)
"UNREGISTER" -> unregisterCommand (ircCmdMsg ircCmd) (ircCmdFrom ircCmd) "UNREGISTER" -> unregisterCommand (ircCmdMsg ircCmd) (ircCmdFrom ircCmd)
_ -> return () _ -> return ()
-- | Process an update command
processUpdateCommand :: IrcCmd -> IrcBot ()
processUpdateCommand ircCmd = do
ircbot <- get
let oldData = ircBotResumeData ircbot
from = ircCmdFrom ircCmd
stuff = ircCmdMsg ircCmd
put $ ircbot { ircBotResumeData = M.insert from stuff oldData }

View file

@ -11,6 +11,7 @@ import Data.Time
import Network import Network
import Prelude hiding (catch) import Prelude hiding (catch)
import System.IO import System.IO
import System.Posix.IO (handleToFd)
import Hsbot.Irc.Command import Hsbot.Irc.Command
import Hsbot.Irc.Config import Hsbot.Irc.Config
@ -18,7 +19,7 @@ import Hsbot.Irc.Message
import Hsbot.Irc.Plugin import Hsbot.Irc.Plugin
import Hsbot.Irc.Server import Hsbot.Irc.Server
import Hsbot.Irc.Types import Hsbot.Irc.Types
import Hsbot.Message (BotMsg) import Hsbot.Message
-- | IrcBot's main entry point -- | IrcBot's main entry point
startIrcbot :: IrcConfig -> Chan BotMsg -> Chan BotMsg -> IO () startIrcbot :: IrcConfig -> Chan BotMsg -> Chan BotMsg -> IO ()
@ -29,8 +30,9 @@ startIrcbot config masterChan myChan = do
putStrLn $ concat ["[IrcBot] Connecting to ", ircConfigAddress config, "... "] putStrLn $ concat ["[IrcBot] Connecting to ", ircConfigAddress config, "... "]
handle <- connectTo (ircConfigAddress config) (ircConfigPort config) handle <- connectTo (ircConfigAddress config) (ircConfigPort config)
hSetBuffering handle NoBuffering hSetBuffering handle NoBuffering
myOwnThreadId <- myThreadId fd <- handleToFd handle
putStrLn "[IrcBot] Spawning reader threads..." putStrLn "[IrcBot] Spawning reader threads..."
myOwnThreadId <- myThreadId
readerThreadId <- forkIO $ ircBotReader handle chan myOwnThreadId readerThreadId <- forkIO $ ircBotReader handle chan myOwnThreadId
masterReaderThreadId <- forkIO $ ircBotMasterReader masterChan chan masterReaderThreadId <- forkIO $ ircBotMasterReader masterChan chan
putStrLn "[IrcBot] Initializing server connection..." putStrLn "[IrcBot] Initializing server connection..."
@ -49,10 +51,13 @@ startIrcbot config masterChan myChan = do
, ircBotHandle = handle , ircBotHandle = handle
, ircBotConfig = config , ircBotConfig = config
, ircBotReaderThreadId = readerThreadId , ircBotReaderThreadId = readerThreadId
, ircBotMasterReaderThreadId = masterReaderThreadId } , ircBotMasterReaderThreadId = masterReaderThreadId
, ircBotResumeData = M.singleton "HANDLE" (show fd) }
ircBotState' <- execStateT (initBotServerConnection config) ircBotState ircBotState' <- execStateT (initBotServerConnection config) ircBotState
putStrLn "[IrcBot] Entering main loop... " putStrLn "[IrcBot] Spawning plugins..."
_ <- ircBotLoop ircBotState' `catch` (\(_ :: IOException) -> return ()) ircBotState'' <- execStateT spawnIrcPlugins ircBotState'
putStrLn "[IrcBot] Entering Core loop... "
_ <- (execStateT ircBotLoop ircBotState'') `catch` (\(_ :: IOException) -> return (ircBotState''))
return () return ()
--resumeIrcBot --resumeIrcBot
@ -89,28 +94,17 @@ initBotServerConnection config = do
ircServerState' <- execStateT (initServerConnection config) ircServerState ircServerState' <- execStateT (initServerConnection config) ircServerState
put $ ircBot { ircBotServerState = ircServerState' } put $ ircBot { ircBotServerState = ircServerState' }
-- | IrcBot's loop that can catch ircbot's states' updates
ircBotLoop :: IrcBotState -> IO ()
ircBotLoop ircBotState = do
putStrLn "[IrcBot] Spawning plugins..."
ircBotState' <- execStateT spawnIrcPlugins ircBotState
-- Todo : throw new ircbotstate to hsbot
putStrLn "[IrcBot] Entering Core loop... "
_ <- (execStateT ircBotCore ircBotState') -- `catch` (\(_ :: NewBotStateException) -> return ircBotState')
return ()
-- TODO : loop!
-- | Run the IrcBot's main loop -- | Run the IrcBot's main loop
ircBotCore :: IrcBot () ircBotLoop :: IrcBot ()
ircBotCore = forever $ do ircBotLoop = forever $ do
ircBot <- get chan <- gets ircBotChan
let chan = ircBotChan ircBot
msg <- liftIO $ readChan chan msg <- liftIO $ readChan chan
case msg of case msg of
InIrcMsg inIrcMsg -> dispatchMessage $ InIrcMsg inIrcMsg InIrcMsg inIrcMsg -> dispatchMessage $ InIrcMsg inIrcMsg
OutIrcMsg outIrcMsg -> sendThisMessage outIrcMsg OutIrcMsg outIrcMsg -> sendThisMessage outIrcMsg
IntIrcCmd intIrcCmd -> do IntIrcCmd intIrcCmd -> do
processInternalCommand $ IntIrcCmd intIrcCmd processInternalCommand $ IntIrcCmd intIrcCmd
reportUpdate
where where
sendThisMessage :: IrcMsg -> IrcBot () sendThisMessage :: IrcMsg -> IrcBot ()
sendThisMessage outputMsg = do sendThisMessage outputMsg = do
@ -143,3 +137,15 @@ dispatchMessage (InIrcMsg inIrcMsg) = do
getMsgContent = unwords . tail $ ircMsgParameters inIrcMsg getMsgContent = unwords . tail $ ircMsgParameters inIrcMsg
dispatchMessage _ = return () dispatchMessage _ = return ()
-- | Reports an update to the master bot
reportUpdate :: IrcBot ()
reportUpdate = do
ircbot <- get
let masterChan = ircBotMasterChan ircbot
msg = IntMsg $ Msg { msgType = "UPDATE"
, msgFrom = ircConfigName $ ircBotConfig ircbot
, msgTo = "CORE"
, msgCmd = show $ ircBotResumeData ircbot
}
liftIO $ writeChan masterChan msg

View file

@ -5,7 +5,7 @@ module Hsbot.Irc.Plugin
, loadIrcPlugin , loadIrcPlugin
, sendToPlugin , sendToPlugin
, spawnIrcPlugins , spawnIrcPlugins
, unloadPlugin , unloadIrcPlugin
) where ) where
import Control.Concurrent import Control.Concurrent
@ -45,16 +45,20 @@ loadIrcPlugin pluginName = do
"Ping" -> ircBotPluginPing "Ping" -> ircBotPluginPing
"Quote" -> ircBotPluginQuote "Quote" -> ircBotPluginQuote
_ -> ircBotPluginDummy _ -> ircBotPluginDummy
let oldPlugins = ircBotPlugins ircbot let oldPlugins = ircBotPlugins ircbot
oldResumeData = ircBotResumeData ircbot
-- We check for unicity -- We check for unicity
case M.lookup pluginName oldPlugins of case M.lookup pluginName oldPlugins of
Just _ -> return () Just _ -> return ()
Nothing -> do Nothing -> do
threadId <- liftIO $ forkIO (entryPoint pluginChan masterChan) threadId <- liftIO $ forkIO (entryPoint pluginChan masterChan)
let plugin = IrcPluginState { ircPluginName = pluginName let plugin = IrcPluginState { ircPluginName = pluginName
, ircPluginChan = pluginChan , ircPluginChan = pluginChan
, ircPluginMasterChan = masterChan } , ircPluginMasterChan = masterChan }
put $ ircbot { ircBotPlugins = M.insert pluginName (plugin, threadId) oldPlugins } newPlugins = M.insert pluginName (plugin, threadId) oldPlugins
newResumeData = M.insert "PLUGINS" (show $ M.keys newPlugins) oldResumeData
put $ ircbot { ircBotPlugins = newPlugins
, ircBotResumeData = newResumeData }
-- | Sends a list of loaded plugins -- | Sends a list of loaded plugins
listPlugins :: IrcMsg -> String -> IrcBot () listPlugins :: IrcMsg -> String -> IrcBot ()
@ -66,14 +70,18 @@ listPlugins originalRequest dest = do
Nothing -> return () Nothing -> return ()
-- | Unloads a plugin -- | Unloads a plugin
unloadPlugin :: String -> IrcBot () unloadIrcPlugin :: String -> IrcBot ()
unloadPlugin name = do unloadIrcPlugin name = do
bot <- get ircbot <- get
let oldPlugins = ircBotPlugins bot let oldPlugins = ircBotPlugins ircbot
oldResumeData = ircBotResumeData ircbot
-- We check if the plugin exists
case M.lookup name oldPlugins of case M.lookup name oldPlugins of
Just (_, threadId) -> do Just (_, threadId) -> do
let newPlugins = M.delete name oldPlugins let newPlugins = M.delete name oldPlugins
newResumeData = M.insert "PLUGINS" (show $ M.keys newPlugins) oldResumeData
liftIO $ throwTo threadId UserInterrupt liftIO $ throwTo threadId UserInterrupt
put $ bot { ircBotPlugins = newPlugins } put $ ircbot { ircBotPlugins = newPlugins
, ircBotResumeData = newResumeData }
Nothing -> return () Nothing -> return ()

View file

@ -21,17 +21,18 @@ type IrcBot = StateT IrcBotState IO
-- | An Ircbot state -- | An Ircbot state
data IrcBotState = IrcBotState data IrcBotState = IrcBotState
{ ircBotStartTime :: UTCTime -- the bot's uptime { ircBotStartTime :: UTCTime -- the bot's uptime
, ircBotPlugins :: M.Map String (IrcPluginState, ThreadId) -- Loaded plugins , ircBotPlugins :: M.Map String (IrcPluginState, ThreadId) -- Loaded plugins
, ircBotCommands :: M.Map String [String] -- Loaded plugins , ircBotCommands :: M.Map String [String] -- Loaded plugins
, ircBotChan :: Chan IrcBotMsg -- The IrcBot's communication channel , ircBotChan :: Chan IrcBotMsg -- The IrcBot's communication channel
, ircBotMasterChan :: Chan BotMsg -- The Hsbot communication channel , ircBotMasterChan :: Chan BotMsg -- The Hsbot communication channel
, ircBotMyChan :: Chan BotMsg -- The Hsbot communication channel , ircBotMyChan :: Chan BotMsg -- The Hsbot communication channel
, ircBotServerState :: IrcServerState -- The state of the IrcServer , ircBotServerState :: IrcServerState -- The state of the IrcServer
, ircBotHandle :: Handle -- The server's socket/handle , ircBotHandle :: Handle -- The server's socket/handle
, ircBotConfig :: IrcConfig -- The starting configuration , ircBotConfig :: IrcConfig -- The starting configuration
, ircBotReaderThreadId :: ThreadId , ircBotReaderThreadId :: ThreadId -- the thread that process inputs from the socket
, ircBotMasterReaderThreadId :: ThreadId , ircBotMasterReaderThreadId :: ThreadId -- the thread that process inputs from the master bot
, ircBotResumeData :: M.Map String String -- the necessary data to resume the bot's operations on reboot
} }
-- | The IrcServer monad -- | The IrcServer monad

View file

@ -1,8 +1,11 @@
module Hsbot.Message module Hsbot.Message
( BotMsg (..) ( BotMsg (..)
, Msg (..) , Msg (..)
, processInternalMessage
) where ) where
import Hsbot.PluginUtils
-- | A hsbot message -- | A hsbot message
data Msg = Msg data Msg = Msg
{ msgType :: String -- the message type { msgType :: String -- the message type

1
TODO
View file

@ -2,6 +2,7 @@
* Handle bot/Plugin state updates threw the masters' Chans * Handle bot/Plugin state updates threw the masters' Chans
* Find a way to handle bot reloading threw exec * Find a way to handle bot reloading threw exec
* Find a way to cleanly handle termination/reboot requests (signals, IOExceptions, plugins' requests)
* write the vote system for the quote module * write the vote system for the quote module
* only the quote reporter should be able to edit it * only the quote reporter should be able to edit it