Fixed the plugin termination.
The master of a plugin will now wait for the plugin it kills to terminate.
This commit is contained in:
parent
9dda7dc1b9
commit
3410caa6f2
6 changed files with 32 additions and 20 deletions
|
@ -12,6 +12,7 @@ import Data.Maybe
|
||||||
import Hsbot.Irc.Message
|
import Hsbot.Irc.Message
|
||||||
import Hsbot.Irc.Plugin
|
import Hsbot.Irc.Plugin
|
||||||
import Hsbot.Irc.Types
|
import Hsbot.Irc.Types
|
||||||
|
import Hsbot.Types
|
||||||
|
|
||||||
-- | Registers a plugin's command
|
-- | Registers a plugin's command
|
||||||
registerCommand :: String -> String -> IrcBot ()
|
registerCommand :: String -> String -> IrcBot ()
|
||||||
|
@ -34,19 +35,19 @@ unregisterCommand cmd pluginName' = do
|
||||||
put $ ircBot { ircBotCommands = newCmds }
|
put $ ircBot { ircBotCommands = newCmds }
|
||||||
|
|
||||||
-- | Processes an internal command
|
-- | Processes an internal command
|
||||||
processInternalCommand :: IrcBotMsg -> IrcBot (Bool)
|
processInternalCommand :: IrcBotMsg -> IrcBot (BotStatus)
|
||||||
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
|
||||||
Just (plugin, _) -> sendToPlugin (IntIrcCmd ircCmd) plugin
|
Just (plugin, _, _) -> sendToPlugin (IntIrcCmd ircCmd) plugin
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
return False
|
return BotContinue
|
||||||
processInternalCommand _ = return (False)
|
processInternalCommand _ = return (BotContinue)
|
||||||
|
|
||||||
-- | Processes a core command
|
-- | Processes a core command
|
||||||
processCoreCommand :: IrcCmd -> IrcBot (Bool)
|
processCoreCommand :: IrcCmd -> IrcBot (BotStatus)
|
||||||
processCoreCommand ircCmd = do
|
processCoreCommand ircCmd = do
|
||||||
let command' = ircCmdCmd ircCmd
|
let command' = ircCmdCmd ircCmd
|
||||||
originalRequest = ircCmdBotMsg ircCmd
|
originalRequest = ircCmdBotMsg ircCmd
|
||||||
|
@ -58,7 +59,9 @@ processCoreCommand ircCmd = do
|
||||||
"UNREGISTER" -> unregisterCommand (ircCmdMsg ircCmd) (ircCmdFrom ircCmd)
|
"UNREGISTER" -> unregisterCommand (ircCmdMsg ircCmd) (ircCmdFrom ircCmd)
|
||||||
"UPDATE" -> processUpdateCommand ircCmd
|
"UPDATE" -> processUpdateCommand ircCmd
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
return $ command' == "REBOOT"
|
if command' == "REBOOT"
|
||||||
|
then return BotReboot
|
||||||
|
else return BotContinue
|
||||||
|
|
||||||
-- | Process an update command
|
-- | Process an update command
|
||||||
processUpdateCommand :: IrcCmd -> IrcBot ()
|
processUpdateCommand :: IrcCmd -> IrcBot ()
|
||||||
|
|
|
@ -110,7 +110,7 @@ ircBotLoop = forever $ do
|
||||||
IntIrcCmd intIrcCmd -> do
|
IntIrcCmd intIrcCmd -> do
|
||||||
reboot <- processInternalCommand $ IntIrcCmd intIrcCmd
|
reboot <- processInternalCommand $ IntIrcCmd intIrcCmd
|
||||||
reportUpdate
|
reportUpdate
|
||||||
if reboot
|
if reboot == BotReboot
|
||||||
then processRebootCommand
|
then processRebootCommand
|
||||||
else return ()
|
else return ()
|
||||||
where
|
where
|
||||||
|
@ -131,9 +131,9 @@ dispatchMessage (InIrcMsg inIrcMsg) = do
|
||||||
let key = tail . head $ words getMsgContent
|
let key = tail . head $ words getMsgContent
|
||||||
pluginNames = fromMaybe [] $ M.lookup key cmds
|
pluginNames = fromMaybe [] $ M.lookup key cmds
|
||||||
plugins' = fromMaybe [] $ mapM (flip M.lookup plugins) pluginNames
|
plugins' = fromMaybe [] $ mapM (flip M.lookup plugins) pluginNames
|
||||||
in mapM_ (sendRunCommand (tail getMsgContent) . fst) plugins'
|
in mapM_ (sendRunCommand (tail getMsgContent) . first) plugins'
|
||||||
else
|
else
|
||||||
mapM_ (sendToPlugin (InIrcMsg inIrcMsg) . fst) (M.elems plugins)
|
mapM_ (sendToPlugin (InIrcMsg inIrcMsg) . first) (M.elems plugins)
|
||||||
where
|
where
|
||||||
isPluginCommand :: IrcConfig -> Bool
|
isPluginCommand :: IrcConfig -> Bool
|
||||||
isPluginCommand config =
|
isPluginCommand config =
|
||||||
|
|
|
@ -52,11 +52,12 @@ loadIrcPlugin pluginName = do
|
||||||
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)
|
mvar <- liftIO newEmptyMVar
|
||||||
|
threadId <- liftIO . forkIO $ finally (entryPoint pluginChan masterChan) (putMVar mvar ())
|
||||||
let plugin = IrcPluginState { ircPluginName = pluginName
|
let plugin = IrcPluginState { ircPluginName = pluginName
|
||||||
, ircPluginChan = pluginChan
|
, ircPluginChan = pluginChan
|
||||||
, ircPluginMasterChan = masterChan }
|
, ircPluginMasterChan = masterChan }
|
||||||
newPlugins = M.insert pluginName (plugin, threadId) oldPlugins
|
newPlugins = M.insert pluginName (plugin, mvar, threadId) oldPlugins
|
||||||
newResumeData = M.insert "PLUGINS" (show $ M.keys newPlugins) oldResumeData
|
newResumeData = M.insert "PLUGINS" (show $ M.keys newPlugins) oldResumeData
|
||||||
put $ ircbot { ircBotPlugins = newPlugins
|
put $ ircbot { ircBotPlugins = newPlugins
|
||||||
, ircBotResumeData = newResumeData }
|
, ircBotResumeData = newResumeData }
|
||||||
|
@ -67,7 +68,7 @@ listPlugins originalRequest dest = do
|
||||||
plugins <- gets ircBotPlugins
|
plugins <- gets ircBotPlugins
|
||||||
let listing = unwords $ M.keys plugins
|
let listing = unwords $ M.keys plugins
|
||||||
case M.lookup dest plugins of
|
case M.lookup dest plugins of
|
||||||
Just (plugin, _) -> sendToPlugin (IntIrcCmd $ IrcCmd "ANSWER" "CORE" dest listing originalRequest) plugin
|
Just (plugin, _, _) -> sendToPlugin (IntIrcCmd $ IrcCmd "ANSWER" "CORE" dest listing originalRequest) plugin
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
|
|
||||||
-- | Unloads a plugin
|
-- | Unloads a plugin
|
||||||
|
@ -87,9 +88,10 @@ killIrcPlugin name = do
|
||||||
let oldPlugins = ircBotPlugins ircbot
|
let oldPlugins = ircBotPlugins ircbot
|
||||||
-- We check if the plugin exists
|
-- We check if the plugin exists
|
||||||
case M.lookup name oldPlugins of
|
case M.lookup name oldPlugins of
|
||||||
Just (_, threadId) -> do
|
Just (_, mvar, threadId) -> do
|
||||||
let newPlugins = M.delete name oldPlugins
|
let newPlugins = M.delete name oldPlugins
|
||||||
liftIO $ throwTo threadId UserInterrupt
|
liftIO $ throwTo threadId UserInterrupt
|
||||||
put $ ircbot { ircBotPlugins = newPlugins }
|
put $ ircbot { ircBotPlugins = newPlugins }
|
||||||
|
liftIO $ takeMVar mvar
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
|
|
||||||
|
|
|
@ -3,6 +3,7 @@ module Hsbot.Irc.Types
|
||||||
, IrcBotState (..)
|
, IrcBotState (..)
|
||||||
, IrcServer
|
, IrcServer
|
||||||
, IrcServerState (..)
|
, IrcServerState (..)
|
||||||
|
, first
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
@ -22,7 +23,7 @@ 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, MVar (), 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
|
||||||
|
@ -44,3 +45,6 @@ data IrcServerState = IrcServerState
|
||||||
, ircServerChan :: Chan IrcBotMsg -- the IrcBot channel
|
, ircServerChan :: Chan IrcBotMsg -- the IrcBot channel
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | Utilities for triplets
|
||||||
|
first :: (a, b, c) -> a
|
||||||
|
first (a, _, _) = a
|
||||||
|
|
|
@ -5,8 +5,9 @@ module Hsbot.Plugin
|
||||||
, unloadPlugin
|
, unloadPlugin
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Concurrent
|
import Control.Concurrent (forkIO)
|
||||||
import Control.Concurrent.Chan ()
|
import Control.Concurrent.Chan
|
||||||
|
import Control.Concurrent.MVar
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -29,12 +30,13 @@ spawnPlugin (IrcBotConfig ircConfig) = do
|
||||||
bot <- get
|
bot <- get
|
||||||
let chan = botChan bot
|
let chan = botChan bot
|
||||||
pchan <- liftIO (newChan :: IO (Chan BotMsg))
|
pchan <- liftIO (newChan :: IO (Chan BotMsg))
|
||||||
threadId <- liftIO $ forkIO (startIrcbot ircConfig chan pchan)
|
mvar <- liftIO newEmptyMVar
|
||||||
|
threadId <- liftIO . forkIO $ finally (startIrcbot ircConfig chan pchan) (putMVar mvar ())
|
||||||
let plugin = PluginState { pluginName = ircConfigName ircConfig
|
let plugin = PluginState { pluginName = ircConfigName ircConfig
|
||||||
, pluginChan = pchan
|
, pluginChan = pchan
|
||||||
, pluginHandles = M.empty }
|
, pluginHandles = M.empty }
|
||||||
plugins = botPlugins bot
|
plugins = botPlugins bot
|
||||||
put $ bot { botPlugins = M.insert (pluginName plugin) (plugin, threadId) plugins }
|
put $ bot { botPlugins = M.insert (pluginName plugin) (plugin, mvar, threadId) plugins }
|
||||||
resumeData <- gets botResumeData
|
resumeData <- gets botResumeData
|
||||||
liftIO $ modifyMVar_ resumeData (\oldData -> return $ M.insert (ircConfigName ircConfig) M.empty oldData)
|
liftIO $ modifyMVar_ resumeData (\oldData -> return $ M.insert (ircConfigName ircConfig) M.empty oldData)
|
||||||
|
|
||||||
|
@ -52,9 +54,10 @@ killPlugin name = do
|
||||||
let oldPlugins = botPlugins bot
|
let oldPlugins = botPlugins bot
|
||||||
-- We check if the plugin exists
|
-- We check if the plugin exists
|
||||||
case M.lookup name oldPlugins of
|
case M.lookup name oldPlugins of
|
||||||
Just (_, threadId) -> do
|
Just (_, mvar, threadId) -> do
|
||||||
let newPlugins = M.delete name oldPlugins
|
let newPlugins = M.delete name oldPlugins
|
||||||
liftIO $ throwTo threadId UserInterrupt
|
liftIO $ throwTo threadId UserInterrupt
|
||||||
put $ bot { botPlugins = newPlugins }
|
put $ bot { botPlugins = newPlugins }
|
||||||
|
liftIO $ takeMVar mvar
|
||||||
Nothing -> return ()
|
Nothing -> return ()
|
||||||
|
|
||||||
|
|
|
@ -27,7 +27,7 @@ type Bot = StateT BotState IO
|
||||||
-- | An Hsbot state
|
-- | An Hsbot state
|
||||||
data BotState = BotState
|
data BotState = BotState
|
||||||
{ botStartTime :: UTCTime -- the bot's uptime
|
{ botStartTime :: UTCTime -- the bot's uptime
|
||||||
, botPlugins :: M.Map String (PluginState, ThreadId) -- Loaded plugins
|
, botPlugins :: M.Map String (PluginState, MVar (), ThreadId) -- Loaded plugins
|
||||||
, botChan :: Chan BotMsg -- the bot's communication channel
|
, botChan :: Chan BotMsg -- the bot's communication channel
|
||||||
, botConfig :: [BotConfig] -- the bot's starting config
|
, botConfig :: [BotConfig] -- the bot's starting config
|
||||||
, botResumeData :: MVar BotResumeData -- the necessary data to resume the bot's operations on reboot
|
, botResumeData :: MVar BotResumeData -- the necessary data to resume the bot's operations on reboot
|
||||||
|
|
Reference in a new issue