Archived
1
0
Fork 0

Reorganized code and types, changed slightly the architecture.

This commit is contained in:
Julien Dessaux 2010-02-04 20:36:58 +01:00
parent 57f559f3a1
commit 884c6c9f2e
10 changed files with 272 additions and 164 deletions

View file

@ -5,7 +5,7 @@ module Config
import Network import Network
import Hsbot.Core import Hsbot.Types
-- | Imported plugins goes there -- | Imported plugins goes there
defaultPlugins :: [String] defaultPlugins :: [String]

View file

@ -5,6 +5,8 @@ module Hsbot
, module Hsbot.IRCParser , module Hsbot.IRCParser
, module Hsbot.Main , module Hsbot.Main
, module Hsbot.Plugin , module Hsbot.Plugin
, module Hsbot.Types
, module Hsbot.Utils
) where ) where
import Config import Config
@ -13,4 +15,6 @@ import Hsbot.IRC
import Hsbot.IRCParser import Hsbot.IRCParser
import Hsbot.Main import Hsbot.Main
import Hsbot.Plugin import Hsbot.Plugin
import Hsbot.Types
import Hsbot.Utils

View file

@ -1,17 +1,6 @@
module Hsbot.Core module Hsbot.Core
( Bot(..) ( connectServer
, Channel(..)
, Config(..)
, IrcServer(..)
, IrcBot
, IrcMsg(..)
, Plugin(..)
, connectServer
, disconnectServer , disconnectServer
, inColor
, serializeIrcMsg
, traceM
, writeMsg
) where ) where
import Control.Concurrent import Control.Concurrent
@ -20,82 +9,11 @@ import Control.Monad.State
import Data.List import Data.List
import Network import Network
import System.IO import System.IO
import System.Plugins import System.Time (getClockTime)
import System.Time (ClockTime, getClockTime)
-- | TODO : a monad for a channel, and a monad for a server, all together driven by a Bot? import Hsbot.IRCParser
import Hsbot.Types
-- | Configuration data type import Hsbot.Utils
data Config = Config {
commandPrefixes :: String, -- command prefixes, for example @[\'>\',\'@\',\'?\']@
ircServer :: IrcServer -- list of 'Server's to connect to
} deriving (Show)
-- | An IRC server
data IrcServer = IrcServer
{ address :: String -- the server's address
, port :: PortID -- the server's port
, channels :: [String] -- a list of channels to join
, nickname :: String -- the hsbot's nickname
, password :: String -- the hsbot's password, optional
, realname :: String -- the hsbot's real name, optional
, administrators :: [String] -- bot admins nicknames
}
instance Show IrcServer where
show (IrcServer a p c n pa r ad) = (show a)
++ (case p of
PortNumber num -> show num
Service s -> show s
UnixSocket u -> show u)
++ (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
type IrcBot a = StateT Bot IO a
-- | An IRC Bot server state
data Bot = Bot
{ serverConfig :: IrcServer -- original server config we are connected to
, startTime :: ClockTime -- the bot's uptime
, botHandle :: Handle -- the socket/handle
, chans :: [Channel] -- the list of channels we have joined
, botPlugins :: [Plugin] -- The list of loaded plugins
, serverChannel :: Chan IrcMsg -- The bot's communication channel
, serverThreadId :: ThreadId -- The bot's thread ID
}
instance Show Bot where
show (Bot _ s h c p _ _) = (show s) ++ (show h) ++ (show c) ++ (show p)
-- | A channel connection
data Channel = Channel
{ channelName :: String -- the channel's name
, channelNick :: String -- our nickname
, channelAdmins :: [String] -- the bot administrators
} deriving (Show)
-- |An IRC message.
data IrcMsg = IrcMsg
{ prefix :: Maybe String -- the message prefix
, command :: String -- the message command
, parameters :: [String] -- the message parameters
} deriving (Show)
-- | A plugin definition
data Plugin = Plugin
{ pluginName :: String -- The plugin's name
, pluginModule :: Module -- The plugin himself
, pluginThreadId :: ThreadId -- The plugin thread
, pluginChannel :: Chan IrcMsg -- The plugin channel
}
instance Show Plugin where
show (Plugin name _ _ _) = show name
-- Connect to the server and return the initial bot state -- Connect to the server and return the initial bot state
connectServer :: IrcServer -> IO Bot connectServer :: IrcServer -> IO Bot
@ -107,57 +25,29 @@ connectServer server = do
hSetBuffering handle NoBuffering hSetBuffering handle NoBuffering
putStrLn "done." putStrLn "done."
putStr $ "Opening server communication channel... " putStr $ "Opening server communication channel... "
chan <- newChan :: IO (Chan IrcMsg) chan <- newChan :: IO (Chan BotMsg)
threadId <- forkIO $ botWriter handle chan threadId <- forkIO $ botReader handle chan
putStrLn "done." putStrLn "done."
return (Bot server starttime handle [] [] chan threadId) return (Bot server starttime handle [] [] chan threadId)
-- | Disconnect from the server -- | Disconnect from the server
disconnectServer :: Bot -> IO () -- IO Bot ? disconnectServer :: Bot -> IO () -- IO Bot ?
disconnectServer bot = do disconnectServer bot = do
killThread $ serverThreadId bot killThread $ readerThreadId bot
mapM_ (killThread . pluginThreadId) (botPlugins bot)
hClose $ botHandle bot hClose $ botHandle bot
return () return ()
-- | Processing loop -- | Socket reading loop
botWriter :: Handle -> Chan IrcMsg -> IO () botReader :: Handle -> Chan BotMsg -> IO ()
botWriter handle chan = forever $ do botReader handle chan = forever $ do
input <- readChan chan :: IO IrcMsg -- TODO : detect end of connection!
sendstr handle (serializeIrcMsg input) str <- hGetLine handle
let msg = parseIrcMsg str
-- | Write an IRC message to the bot's writer case msg of
writeMsg :: IrcMsg -> IrcBot () Right msg' -> do
writeMsg msg = do trace $ inColor ("<-- " ++ (show msg')) [33]
chan <- gets serverChannel writeChan chan (InputMsg msg')
liftIO $ writeChan chan msg _ -> do
return ()
-- |Serialize an IRC message to a string.
serializeIrcMsg :: IrcMsg -> String
serializeIrcMsg (IrcMsg pfx cmd params) = pfxStr ++ cmd ++ paramStr
where pfxStr = case pfx of
Nothing -> ""
Just pfx' -> ":" ++ pfx' ++ " "
paramStr = concat (map paramToStr (init params)
++ [lastParamToStr (last params)])
paramToStr p = " " ++ p
lastParamToStr p = " :" ++ p
-- | Send a string over handle
sendstr :: Handle -> String -> IO ()
sendstr handle str = do
trace $ inColor ("--> " ++ str) [33]
hPutStr handle (str ++ "\r\n")
-- | Log a message string
trace :: String -> IO ()
trace msg = putStrLn msg
-- | Log a message string
traceM :: String -> IrcBot ()
traceM msg = liftIO $ putStrLn msg
-- |Wrap a string with ANSI escape sequences.
inColor :: String -> [Int] -> String
inColor str vals = "\ESC[" ++ valstr ++ "m" ++ str ++ "\ESC[0m"
where valstr = concat $ intersperse ";" $ map show vals

View file

@ -5,50 +5,38 @@ module Hsbot.IRC
import Control.Concurrent.Chan import Control.Concurrent.Chan
import Control.Monad.State import Control.Monad.State
import System.IO
import Hsbot.Core
import Hsbot.IRCParser import Hsbot.IRCParser
import Hsbot.Plugin
import Hsbot.Types
import Hsbot.Utils
-- | Setup a newly connected server by sending nick and join stuff -- | Setup a newly connected server by sending nick and join stuff
initServer :: IrcBot () initServer :: IrcBot ()
initServer = do initServer = do
server <- gets serverConfig server <- gets serverConfig
writeMsg $ IrcMsg Nothing "NICK" [(nickname server)] sendstr $ serializeIrcMsg $ IrcMsg Nothing "NICK" [(nickname server)]
writeMsg $ 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
writeMsg $ IrcMsg Nothing "PRIVMSG" ["nickserv", "identify", (password server)] sendstr $ serializeIrcMsg $ IrcMsg Nothing "PRIVMSG" ["nickserv", "identify", (password server)]
joinChans mapM_ joinChan (channels server)
return ()
-- | Run a server -- | Run a server
runServer :: IrcBot () runServer :: IrcBot ()
runServer = do runServer = do
handle <- gets botHandle chan <- gets botChannel
plugins <- gets botPlugins plugins <- gets botPlugins
str <- liftIO $ hGetLine handle let input = readChan chan
traceM $ inColor ("<-- " ++ str) [33] msg <- liftIO input
let msg = parseIrcMsg str
case msg of case msg of
Right msg' -> do InputMsg inputMsg ->
mapM_ (sendPlugin msg') plugins mapM_ (sendToPlugin $ InputMsg inputMsg) plugins
return () OutputMsg outputMsg ->
_ -> do sendstr (serializeIrcMsg outputMsg)
return () InternalCmd internalCmd ->
traceM $ show msg traceM "TODO"
runServer runServer
sendPlugin :: IrcMsg -> Plugin -> IrcBot ()
sendPlugin msg plugin = do
let chan = pluginChannel plugin
liftIO $ writeChan chan msg
-- | Join chans
joinChans :: IrcBot ()
joinChans = do
server <- gets serverConfig
mapM_ joinChan (channels server)
-- | Joins a chan -- | Joins a chan
joinChan :: String -> IrcBot () joinChan :: String -> IrcBot ()
joinChan name = do joinChan name = do
@ -57,7 +45,6 @@ joinChan name = do
newChannel = Channel name newChannel = Channel name
(nickname $ serverConfig bot) (nickname $ serverConfig bot)
(administrators $ serverConfig bot) (administrators $ serverConfig bot)
traceM $ " Joining " ++ name sendstr $ serializeIrcMsg $ IrcMsg Nothing "JOIN" [name]
writeMsg $ IrcMsg Nothing "JOIN" [name]
put $ bot { chans = newChannel : oldChannels } put $ bot { chans = newChannel : oldChannels }

View file

@ -1,13 +1,13 @@
module Hsbot.IRCParser module Hsbot.IRCParser
( ParseError ( ParseError
, parseIrcMsg , parseIrcMsg
, serializeIrcMsg
) where ) where
import Control.Monad.Identity import Control.Monad.Identity
-- import Data.List
import Text.Parsec import Text.Parsec
import Hsbot.Core import Hsbot.Types
-- | Parses an IrcInput -- | Parses an IrcInput
parseIrcMsg :: String -> Either ParseError IrcMsg parseIrcMsg :: String -> Either ParseError IrcMsg
@ -38,3 +38,14 @@ pLongParam = char ':' >> (many1 (noneOf "\r"))
pShortParam :: ParsecT String u Identity [Char] pShortParam :: ParsecT String u Identity [Char]
pShortParam = many1 (noneOf " \r") pShortParam = many1 (noneOf " \r")
-- |Serialize an IRC message to a string.
serializeIrcMsg :: IrcMsg -> String
serializeIrcMsg (IrcMsg pfx cmd params) = pfxStr ++ cmd ++ paramStr
where pfxStr = case pfx of
Nothing -> ""
Just pfx' -> ":" ++ pfx' ++ " "
paramStr = concat (map paramToStr (init params)
++ [lastParamToStr (last params)])
paramToStr p = " " ++ p
lastParamToStr p = " :" ++ p

View file

@ -9,6 +9,7 @@ import Config
import Hsbot.Core import Hsbot.Core
import Hsbot.IRC import Hsbot.IRC
import Hsbot.Plugin import Hsbot.Plugin
import Hsbot.Types
-- | Bot's main entry point -- | Bot's main entry point
imain :: IO () imain :: IO ()

56
Hsbot/Plugin.hs Normal file
View file

@ -0,0 +1,56 @@
module Hsbot.Plugin
( loadPlugin
, sendToPlugin
) where
import Control.Concurrent
import Control.Concurrent.Chan
import Control.Monad.State
import System.IO
import System.Plugins
import Hsbot.Types
import Hsbot.Utils
-- | Loads a plugin into an ircBot
loadPlugin :: String -> IrcBot ()
loadPlugin name = do
bot <- get
plugin <- liftIO $ effectivelyLoadPlugin name (botChannel bot)
case plugin of
Just plugin' -> do
let oldPlugins = botPlugins bot
put $ bot { botPlugins = plugin' : oldPlugins } -- TODO : clean with a correct append
Nothing -> return ()
-- | Effectively try to load a plugin
effectivelyLoadPlugin :: String -> Chan BotMsg -> IO (Maybe Plugin)
effectivelyLoadPlugin name serverChan = do
-- TODO : test if Plugins/ ++ name ++ .hs exists
-- Just load, do not compile if .o already present
m <- liftIO $ makeAll ("Plugins/" ++ name ++ ".hs") []
plugin <- case m of
MakeSuccess _ _ -> do
ldstat <- load_ ("Plugins/" ++ name ++ ".o") [".","Hsbot","Hsbot/Plugins"] ("main" ++ name)
case ldstat of
LoadSuccess v entryPoint -> do
putStrLn $ inColor ("Loaded plugin: " ++ name) [32]
chan <- newChan :: IO (Chan BotMsg)
threadId <- forkIO $ entryPoint serverChan chan
return $ Just (Plugin name v threadId chan)
LoadFailure e -> do
putStrLn $ inColor ("Couldn't load plugin: " ++ name) [31]
mapM_ putStrLn e
return Nothing
MakeFailure e -> do
putStrLn $ inColor ("FATAL: Couldn't compile plugin: " ++ name) [31]
mapM_ putStrLn e
return Nothing
return plugin
-- | Sends a msg to a plugin
sendToPlugin :: BotMsg -> Plugin -> IrcBot ()
sendToPlugin msg plugin = do
let chan = pluginChannel plugin
liftIO $ writeChan chan msg

104
Hsbot/Types.hs Normal file
View file

@ -0,0 +1,104 @@
module Hsbot.Types
( Bot(..)
, BotMsg(..)
, Channel(..)
, Config(..)
, IntCmd(..)
, IrcServer(..)
, IrcBot
, IrcMsg(..)
, Plugin(..)
) where
import Control.Concurrent
import Control.Concurrent.Chan
import Control.Monad.State
import qualified Data.Map as M
import Network
import System.IO
import System.Plugins
import System.Time (ClockTime)
-- | TODO : a monad for a channel, and a monad for a server, all together driven by a Bot?
-- | Configuration data type
data Config = Config {
commandPrefixes :: String, -- command prefixes, for example @[\'>\',\'@\',\'?\']@
ircServer :: IrcServer -- list of 'Server's to connect to
} deriving (Show)
-- | An IRC server
data IrcServer = IrcServer
{ address :: String -- the server's address
, port :: PortID -- the server's port
, channels :: [String] -- a list of channels to join
, nickname :: String -- the hsbot's nickname
, password :: String -- the hsbot's password, optional
, realname :: String -- the hsbot's real name, optional
, administrators :: [String] -- bot admins nicknames
}
instance Show IrcServer where
show (IrcServer a p c n pa r ad) = (show a)
++ (case p of
PortNumber num -> show num
Service s -> show s
UnixSocket u -> show u)
++ (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
type IrcBot a = StateT Bot IO a
-- | An IRC Bot server state
data Bot = Bot
{ serverConfig :: IrcServer -- original server config we are connected to
, startTime :: ClockTime -- the bot's uptime
, botHandle :: Handle -- the socket/handle
, chans :: [Channel] -- the list of channels we have joined
, botPlugins :: M.Map String Plugin -- Loaded plugins
, botChannel :: Chan BotMsg -- The bot's communication channel
, readerThreadId :: ThreadId -- The bot's thread ID
, botCommands :: M.Map String [String] -- Registered commands ("command", ["pluginName"])
}
instance Show Bot where
show (Bot _ s h c p _ _ cmds) = (show s) ++ (show h) ++ (show c) ++ (show p) ++ (show cmds)
-- | A channel connection
data Channel = Channel
{ channelName :: String -- the channel's name
, channelNick :: String -- our nickname
, channelAdmins :: [String] -- the bot administrators
} deriving (Show)
-- | A Bot command
data IntCmd = IntCmd
{ intCmd :: String -- the bot's internal command
, intCmdParams :: [String] -- the parameters
} deriving (Show)
-- |An IRC message.
data IrcMsg = IrcMsg
{ prefix :: Maybe String -- the message prefix
, command :: String -- the message command
, parameters :: [String] -- the message parameters
} deriving (Show)
-- | A plugin definition
data Plugin = Plugin
{ pluginName :: String -- The plugin's name
, pluginModule :: Module -- The plugin himself
, pluginThreadId :: ThreadId -- The plugin thread
, pluginChannel :: Chan BotMsg -- The plugin channel
}
instance Show Plugin where
show (Plugin name _ _ _) = show name
data BotMsg = InputMsg IrcMsg | OutputMsg IrcMsg | InternalCmd IntCmd

33
Hsbot/Utils.hs Normal file
View file

@ -0,0 +1,33 @@
module Hsbot.Utils
( inColor
, sendstr
, trace
, traceM
) where
import Control.Monad.State
import Data.List
import System.IO
import Hsbot.Types
-- |Wrap a string with ANSI escape sequences.
inColor :: String -> [Int] -> String
inColor str vals = "\ESC[" ++ valstr ++ "m" ++ str ++ "\ESC[0m"
where valstr = concat $ intersperse ";" $ map show vals
-- | Sends a string over handle
sendstr :: String -> IrcBot ()
sendstr str = do
handle <- gets botHandle
traceM $ inColor ("--> " ++ str) [33]
liftIO $ hPutStr handle (str ++ "\r\n")
-- | Log a message string
trace :: String -> IO ()
trace msg = putStrLn msg
-- | Log a message string
traceM :: String -> IrcBot ()
traceM msg = liftIO $ putStrLn msg

22
Plugins/Ping.hs Normal file
View file

@ -0,0 +1,22 @@
module Plugins.Ping
( mainPing
) where
import Control.Concurrent.Chan
import Hsbot.Types
mainPing :: Chan BotMsg -> Chan BotMsg -> IO ()
mainPing serverChan chan = do
loop
where
loop = do
input <- readChan chan
eval input
loop
eval :: BotMsg -> IO ()
eval (InputMsg msg)
| (command msg) == "PING" = writeChan serverChan $ OutputMsg $ IrcMsg Nothing "PONG" (parameters msg)
| otherwise = return ()
eval _ = return ()