Archived
1
0
Fork 0

Some refactoring + cosmetics.

This commit is contained in:
Julien Dessaux 2010-04-25 16:43:01 +02:00
parent 727adadc28
commit b6d119cf5b
13 changed files with 71 additions and 63 deletions

View file

@ -16,7 +16,7 @@ localhost :: IrcServer
localhost = IrcServer localhost = IrcServer
{ serverAddress = "localhost" { serverAddress = "localhost"
, serverPort = PortNumber 6667 , serverPort = PortNumber 6667
, joinChannels = ["#shbot"] , joinChannels = ["#shbot", "#geek"]
, nickname = "hsbot" , nickname = "hsbot"
, password = "" , password = ""
, realname = "The One True bot, with it's haskell soul." , realname = "The One True bot, with it's haskell soul."

View file

@ -42,7 +42,7 @@ dispatchMessage (InputMsg inputMsg)
| isPluginCommand = do | isPluginCommand = do
plugins <- gets botPlugins plugins <- gets botPlugins
cmds <- gets botCommands cmds <- gets botCommands
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
mapM_ (sendRunCommand $ tail getMsgContent) plugins' mapM_ (sendRunCommand $ tail getMsgContent) plugins'
@ -56,7 +56,7 @@ dispatchMessage (InputMsg inputMsg)
, (head getMsgContent) == (commandPrefix config) ] , (head getMsgContent) == (commandPrefix config) ]
sendRunCommand :: String -> Plugin -> IrcBot () sendRunCommand :: String -> Plugin -> IrcBot ()
sendRunCommand cmd plugin = do sendRunCommand cmd plugin = do
sendToPlugin (InternalCmd $ IntCmd "RUN" "CORE" (pluginName plugin) cmd (Just inputMsg)) plugin sendToPlugin (InternalCmd $ IntCmd "RUN" "CORE" (pluginName plugin) cmd inputMsg) plugin
getMsgContent :: String getMsgContent :: String
getMsgContent = unwords . tail $ parameters inputMsg getMsgContent = unwords . tail $ parameters inputMsg
dispatchMessage _ = return () dispatchMessage _ = return ()

View file

@ -5,7 +5,7 @@ module Hsbot.Core
import Control.Concurrent import Control.Concurrent
import Control.Concurrent.Chan() import Control.Concurrent.Chan()
import Control.Exception import Control.Exception(IOException, catch)
import Control.Monad.State import Control.Monad.State
import Data.List() import Data.List()
import qualified Data.Map as M import qualified Data.Map as M
@ -44,10 +44,10 @@ disconnectServer = do
mapM_ unloadPlugin (M.keys $ botPlugins bot) mapM_ unloadPlugin (M.keys $ botPlugins bot)
liftIO $ putStrLn"done." liftIO $ putStrLn"done."
liftIO $ putStr "Closing server communication channel... " liftIO $ putStr "Closing server communication channel... "
liftIO $ killThread $ readerThreadId bot liftIO . killThread $ readerThreadId bot
liftIO $ putStrLn "done." liftIO $ putStrLn "done."
liftIO $ putStr $ "Disconnecting from " ++ name ++ "... " liftIO . putStr $ "Disconnecting from " ++ name ++ "... "
liftIO $ hClose $ botHandle bot liftIO . hClose $ botHandle bot
liftIO $ putStrLn "done." liftIO $ putStrLn "done."
-- | Socket reading loop -- | Socket reading loop

View file

@ -15,10 +15,10 @@ import Hsbot.Utils
initServer :: IrcBot () initServer :: IrcBot ()
initServer = do initServer = do
server <- gets serverConfig server <- gets serverConfig
sendstr $ serializeIrcMsg $ IrcMsg Nothing "NICK" [(nickname server)] sendstr . serializeIrcMsg $ IrcMsg Nothing "NICK" [(nickname server)]
sendstr $ serializeIrcMsg $ IrcMsg Nothing "USER" [(nickname server), "0", "*", (realname server)] sendstr . serializeIrcMsg $ IrcMsg Nothing "USER" [(nickname server), "0", "*", (realname server)]
when (not . null $ password server) $ do when (not . null $ password server) $ do
sendstr $ serializeIrcMsg $ IrcMsg Nothing "PRIVMSG" ["nickserv", "identify", (password server)] sendstr . serializeIrcMsg $ IrcMsg Nothing "PRIVMSG" ["nickserv", "identify", (password server)]
mapM_ joinChan (joinChannels server) mapM_ joinChan (joinChannels server)
-- | Run a server -- | Run a server
@ -40,6 +40,6 @@ joinChan name = do
newChannel = Channel name newChannel = Channel name
(nickname $ serverConfig bot) (nickname $ serverConfig bot)
(administrators $ serverConfig bot) (administrators $ serverConfig bot)
sendstr $ serializeIrcMsg $ IrcMsg Nothing "JOIN" [name] sendstr . serializeIrcMsg $ IrcMsg Nothing "JOIN" [name]
put $ bot { chans = newChannel : oldChannels } put $ bot { chans = newChannel : oldChannels }

View file

@ -18,7 +18,7 @@ pMsg = do
pfx <- optionMaybe pPrefix pfx <- optionMaybe pPrefix
cmd <- pCommand cmd <- pCommand
params <- many (char ' ' >> (pLongParam <|> pShortParam)) params <- many (char ' ' >> (pLongParam <|> pShortParam))
char '\r' _ <- char '\r'
--eof --eof
return $ IrcMsg pfx cmd params return $ IrcMsg pfx cmd params

View file

@ -1,5 +1,7 @@
module Hsbot.IRCPlugin module Hsbot.IRCPlugin
( answerMsg ( IrcPlugin
, PluginState(..)
, answerMsg
, readMsg , readMsg
, sendCommand , sendCommand
, sendCommandWithRequest , sendCommandWithRequest
@ -14,6 +16,16 @@ import Data.Maybe(fromMaybe)
import Hsbot.Types import Hsbot.Types
-- | The IrcPlugin monad
type IrcPlugin a = StateT PluginState IO a
-- | An IRCPlugin state
data PluginState = PluginState
{ instanceName :: String -- The plugin's name
, instanceServerChan :: Chan BotMsg -- The server channel
, instanceChan :: Chan BotMsg -- The plugin channel
}
-- | Basic input output for IrcPlugins -- | Basic input output for IrcPlugins
readMsg :: IrcPlugin (BotMsg) readMsg :: IrcPlugin (BotMsg)
readMsg = do readMsg = do
@ -24,26 +36,25 @@ readMsg = do
writeMsg :: BotMsg -> IrcPlugin () writeMsg :: BotMsg -> IrcPlugin ()
writeMsg botMsg = do writeMsg botMsg = do
serverChan <- gets instanceServerChan serverChan <- gets instanceServerChan
liftIO $ writeChan serverChan $ botMsg liftIO . writeChan serverChan $ botMsg
answerMsg :: Maybe IrcMsg -> String -> IrcPlugin () answerMsg :: IrcMsg -> String -> IrcPlugin ()
answerMsg request msg = do answerMsg request msg = do
let incoming = fromMaybe (IrcMsg Nothing "ARGH" []) request let chanOrigin = head $ parameters request
chanOrigin = head $ parameters (incoming) sender = takeWhile (/= '!') $ fromMaybe "" (prefix request)
sender = takeWhile (/= '!') $ fromMaybe "ARGH" (prefix incoming)
case head chanOrigin of case head chanOrigin of
'#' -> writeMsg $ OutputMsg $ IrcMsg Nothing "PRIVMSG" [chanOrigin, msg] '#' -> writeMsg . OutputMsg $ IrcMsg Nothing "PRIVMSG" [chanOrigin, msg]
_ -> writeMsg $ OutputMsg $ IrcMsg Nothing "PRIVMSG" [sender, msg] _ -> writeMsg . OutputMsg $ IrcMsg Nothing "PRIVMSG" [sender, msg]
-- | Commands management -- | Commands management
sendCommand :: String -> String -> String -> IrcPlugin () sendCommand :: String -> String -> String -> IrcPlugin ()
sendCommand cmd to params = sendCommandWithRequest cmd to params Nothing sendCommand cmd to params = sendCommandWithRequest cmd to params emptyIrcMsg
sendCommandWithRequest :: String -> String -> String -> Maybe IrcMsg -> IrcPlugin () sendCommandWithRequest :: String -> String -> String -> IrcMsg -> IrcPlugin ()
sendCommandWithRequest cmd to params originalRequest = do sendCommandWithRequest cmd to params originalRequest = do
serverChan <- gets instanceServerChan serverChan <- gets instanceServerChan
from <- gets instanceName from <- gets instanceName
liftIO $ writeChan serverChan $ InternalCmd $ IntCmd cmd from to params originalRequest liftIO . writeChan serverChan . InternalCmd $ IntCmd cmd from to params originalRequest
sendRegisterCommand :: String -> IrcPlugin () sendRegisterCommand :: String -> IrcPlugin ()
sendRegisterCommand cmd = sendCommand "REGISTER" "CORE" cmd sendRegisterCommand cmd = sendCommand "REGISTER" "CORE" cmd

View file

@ -33,7 +33,7 @@ effectivelyLoadPlugin name entryPoint serverChan = do
return $ Plugin name threadId chan return $ Plugin name threadId chan
-- | Sends a list of loaded plugins -- | Sends a list of loaded plugins
listPlugins :: Maybe IrcMsg -> String -> IrcBot () listPlugins :: IrcMsg -> String -> IrcBot ()
listPlugins originalRequest dest = do listPlugins originalRequest dest = do
plugins <- gets botPlugins plugins <- gets botPlugins
let listing = unwords $ M.keys plugins let listing = unwords $ M.keys plugins

View file

@ -7,9 +7,8 @@ module Hsbot.Types
, IrcServer(..) , IrcServer(..)
, IrcBot , IrcBot
, IrcMsg(..) , IrcMsg(..)
, IrcPlugin
, Plugin(..) , Plugin(..)
, PluginInstance(..) , emptyIrcMsg
) where ) where
import Control.Concurrent import Control.Concurrent
@ -47,11 +46,6 @@ instance Show IrcServer where
UnixSocket u -> show u) UnixSocket u -> show u)
++ (show c) ++ (show n) ++ (show pa) ++ (show r) ++ (show ad) ++ (show c) ++ (show n) ++ (show pa) ++ (show r) ++ (show ad)
-- instance Show PortID where
-- show (PortNumber n) = show n
-- show (Service s) = show s
-- show (UnixSocket g) = show g
-- | The IrcBot monad -- | The IrcBot monad
type IrcBot a = StateT Bot IO a type IrcBot a = StateT Bot IO a
@ -68,11 +62,11 @@ data Bot = Bot
} }
instance Show Bot where instance Show Bot where
show (Bot _ s h c p _ _ cmds) = "Start time : " ++ (show s) ++ "\n" show (Bot _ s h c p _ _ cmds) = unlines [ "Start time : " ++ (show s)
++ "Handle : " ++ (show h) ++ "\n" , "Handle : " ++ (show h)
++ "Channels : " ++ (show c) ++ "\n" , "Channels : " ++ (show c)
++ "Plugins : " ++ (show p) ++ "\n" , "Plugins : " ++ (show p)
++ "Commands : " ++ (show cmds) ++ "\n" , "Commands : " ++ (show cmds)]
-- | A channel connection -- | A channel connection
data Channel = Channel data Channel = Channel
@ -88,13 +82,16 @@ data IrcMsg = IrcMsg
, parameters :: [String] -- the message parameters , parameters :: [String] -- the message parameters
} deriving (Show) } deriving (Show)
emptyIrcMsg :: IrcMsg
emptyIrcMsg = IrcMsg Nothing "" []
-- | An internal command -- | An internal command
data IntCmd = IntCmd data IntCmd = IntCmd
{ intCmdCmd :: String -- the internal command { intCmdCmd :: String -- the internal command
, intCmdFrom :: String -- who issues it , intCmdFrom :: String -- who issues it
, intCmdTo :: String -- who it is destinated to , intCmdTo :: String -- who it is destinated to
, intCmdMsg :: String -- the message to be transfered , intCmdMsg :: String -- the message to be transfered
, intCmdBotMsg :: Maybe IrcMsg -- An IrcMsg attached to the command , intCmdBotMsg :: IrcMsg -- An IrcMsg attached to the command
} deriving (Show) } deriving (Show)
data BotMsg = InputMsg IrcMsg | OutputMsg IrcMsg | InternalCmd IntCmd deriving (Show) data BotMsg = InputMsg IrcMsg | OutputMsg IrcMsg | InternalCmd IntCmd deriving (Show)
@ -109,13 +106,3 @@ data Plugin = Plugin
instance Show Plugin where instance Show Plugin where
show (Plugin name _ _) = show name show (Plugin name _ _) = show name
-- | A IrcPlugin ("user" side)
data PluginInstance = PluginInstance
{ instanceName :: String -- The plugin's name
, instanceServerChan :: Chan BotMsg -- The server channel
, instanceChan :: Chan BotMsg -- The plugin channel
}
-- | The IrcPlugin monad
type IrcPlugin a = StateT PluginInstance IO a

View file

@ -16,7 +16,7 @@ import Hsbot.Types
-- |Wrap a string with ANSI escape sequences. -- |Wrap a string with ANSI escape sequences.
inColor :: String -> [Int] -> String inColor :: String -> [Int] -> String
inColor str vals = "\ESC[" ++ valstr ++ "m" ++ str ++ "\ESC[0m" inColor str vals = "\ESC[" ++ valstr ++ "m" ++ str ++ "\ESC[0m"
where valstr = concat $ intersperse ";" $ map show vals where valstr = concat . intersperse ";" $ map show vals
-- | Sends a string over handle -- | Sends a string over handle
sendstr :: String -> IrcBot () sendstr :: String -> IrcBot ()

View file

@ -5,7 +5,6 @@ module Plugins.Core
import Control.Concurrent.Chan(Chan) import Control.Concurrent.Chan(Chan)
import Control.Exception import Control.Exception
import Control.Monad.State import Control.Monad.State
import Data.Maybe(fromMaybe)
import Prelude hiding (catch) import Prelude hiding (catch)
import Hsbot.IRCPlugin import Hsbot.IRCPlugin
@ -15,7 +14,7 @@ import Hsbot.Utils
-- | The plugin's main entry point -- | The plugin's main entry point
mainCore :: Chan BotMsg -> Chan BotMsg -> IO () mainCore :: Chan BotMsg -> Chan BotMsg -> IO ()
mainCore serverChan chan = do mainCore serverChan chan = do
let plugin = PluginInstance "Core" serverChan chan let plugin = PluginState "Core" serverChan chan
evalStateT (mapM_ sendRegisterCommand ["list", "load", "reload", "unload"]) plugin evalStateT (mapM_ sendRegisterCommand ["list", "load", "reload", "unload"]) plugin
plugin' <- (execStateT run plugin) `catch` (\(_ :: AsyncException) -> return plugin) plugin' <- (execStateT run plugin) `catch` (\(_ :: AsyncException) -> return plugin)
evalStateT (mapM_ sendUnregisterCommand ["list", "load", "reload", "unload"]) plugin' evalStateT (mapM_ sendUnregisterCommand ["list", "load", "reload", "unload"]) plugin'
@ -36,15 +35,15 @@ run = forever $ do
"load" -> loadPlugin $ tail stuff "load" -> loadPlugin $ tail stuff
"reload" -> reloadPlugin $ tail stuff "reload" -> reloadPlugin $ tail stuff
"unload" -> unloadPlugin $ tail stuff "unload" -> unloadPlugin $ tail stuff
_ -> lift $ trace $ show intCmd -- TODO : help message _ -> lift . trace $ show intCmd -- TODO : help message
"ANSWER" -> let stuff = intCmdMsg intCmd "ANSWER" -> let stuff = intCmdMsg intCmd
in answerMsg request ("Loaded plugins : " ++ stuff) in answerMsg request ("Loaded plugins : " ++ stuff)
_ -> lift $ trace $ show intCmd _ -> lift . trace $ show intCmd
eval (InputMsg _) = return () eval (InputMsg _) = return ()
eval _ = return () eval _ = return ()
-- | The list command -- | The list command
listPlugins :: Maybe IrcMsg -> IrcPlugin () listPlugins :: IrcMsg -> IrcPlugin ()
listPlugins request = do listPlugins request = do
sendCommandWithRequest "LIST" "CORE" (unwords []) request sendCommandWithRequest "LIST" "CORE" (unwords []) request

View file

@ -13,7 +13,7 @@ import Hsbot.Types
-- | The plugin's main entry point -- | The plugin's main entry point
mainPing :: Chan BotMsg -> Chan BotMsg -> IO () mainPing :: Chan BotMsg -> Chan BotMsg -> IO ()
mainPing serverChan chan = do mainPing serverChan chan = do
let plugin = PluginInstance "Ping" serverChan chan let plugin = PluginState "Ping" serverChan chan
_ <- (execStateT run plugin) `catch` (\(_ :: AsyncException) -> return plugin) _ <- (execStateT run plugin) `catch` (\(_ :: AsyncException) -> return plugin)
return () return ()

View file

@ -29,9 +29,9 @@ type QuoteBot a = StateT QuoteDB IO a
-- | The plugin's main entry point -- | The plugin's main entry point
mainQuote :: Chan BotMsg -> Chan BotMsg -> IO () mainQuote :: Chan BotMsg -> Chan BotMsg -> IO ()
mainQuote serverChan chan = do mainQuote serverChan chan = do
let plugin = PluginInstance "Quote" serverChan chan let plugin = PluginState "Quote" serverChan chan
evalStateT (mapM_ sendRegisterCommand ["quote"]) plugin evalStateT (mapM_ sendRegisterCommand ["quote"]) plugin
(execStateT run plugin) `catch` (\(ex :: AsyncException) -> return plugin) _ <- (evalStateT (run quoteBot) plugin) `catch` (\(_ :: AsyncException) -> return quoteBot)
evalStateT (mapM_ sendUnregisterCommand ["quote"]) plugin evalStateT (mapM_ sendUnregisterCommand ["quote"]) plugin
-- | The IrcPlugin monad main function -- | The IrcPlugin monad main function

17
TODO
View file

@ -1,10 +1,21 @@
:julien!~julien@ogu21.corp PRIVMSG #shbot :@quote graou snif :julien!~julien@ogu21.corp PRIVMSG #shbot :@quote graou snif
* Write the quote module * Write the quote module
* clean the plugin module * write the vote system for the quote module
* part chan * only the quote reporter should be able to edit it
* detect too identical quoting in a raw, or implement quote abort
* handle the case we attempt to quote on an empty database
* solve the multiquote problem about the quote owner (with a quoteElem data structure)
* find a better way to track who voted for what?
* add admin checks for cmds * write the help module
* clean the plugin module
* clean cleaning for the quote module
* write a channel tracking plugin. Write the part chan command
* add a plugin for admin checks and tracking
* add the quoteadm command to the quote module
* add a plugin for timer functionnalities other plugin could subscribe to (the troll plugin).
* add register for casual conversations for plugins? * add register for casual conversations for plugins?
* add a "I have stuff to save so don't kill me too hard" status for plugins * add a "I have stuff to save so don't kill me too hard" status for plugins