Archived
1
0
Fork 0

Added the IRCParser (thx galdor), and PrivMsg handling (simply repeat)

This commit is contained in:
Julien Dessaux 2009-08-13 00:07:08 +02:00
parent 65646eb07f
commit dfd0b3dcd7
4 changed files with 78 additions and 19 deletions

View file

@ -2,11 +2,13 @@ module Hsbot
( module Config ( module Config
, module Hsbot.Core , module Hsbot.Core
, module Hsbot.IRC , module Hsbot.IRC
, module Hsbot.IRCParser
, module Hsbot.Main , module Hsbot.Main
) where ) where
import Config import Config
import Hsbot.Core import Hsbot.Core
import Hsbot.IRC import Hsbot.IRC
import Hsbot.IRCParser
import Hsbot.Main import Hsbot.Main

View file

@ -5,15 +5,18 @@ module Hsbot.IRC
, parseIrcMsg , parseIrcMsg
, ping , ping
, pong , pong
, sendPrivmsg
)where )where
import Control.Monad import Control.Monad
import Data.List(isPrefixOf) import Data.List(isPrefixOf)
import Data.Maybe
import Network import Network
import qualified Network.IRC as IRC import qualified Network.IRC as IRC
import System.IO import System.IO
import Hsbot.Core import Hsbot.Core
import Hsbot.IRCParser
type User = String type User = String
type Channel = String type Channel = String
@ -21,7 +24,7 @@ type Command = String
type Args = [String] type Args = [String]
-- | An IRC line -- | An IRC line
data IrcLine = Str String -- a regular string data IrcLine = Privmsg (String, [String]) -- statement (chan, sentence...)
| Quit (IrcServer, Handle) -- a quit message from a server | Quit (IrcServer, Handle) -- a quit message from a server
| Join (IrcServer, Channel) -- joined a channel | Join (IrcServer, Channel) -- joined a channel
| Part (IrcServer, Channel) -- parted the channel | Part (IrcServer, Channel) -- parted the channel
@ -31,8 +34,21 @@ data IrcLine = Str String -- a regular string
deriving (Eq,Show) deriving (Eq,Show)
-- | Parses an IrcInput -- | Parses an IrcInput
parseIrcMsg :: String -> IrcInput parseIrcMsg :: String -> IrcLine
parseIrcMsg str = (Cmd "user" "channel" (str, Just "args")) parseIrcMsg str =
case (ircParser str) of
Left err -> Nil
Right x -> eval x
where
eval :: IrcMsg -> IrcLine
eval x@(IrcMsg statement cmd stuff)
| cmd == "PING" = Ping $ head stuff
| cmd == "PRIVMSG" =
case statement of
Nothing -> Nil
Just statement' -> if stuff!!1 == "reboot" then Reboot
else Privmsg $ (statement', stuff)
| otherwise = Nil
-- | Connects to a server -- | Connects to a server
connectServer :: IrcServer -> IO (IrcServer, Handle) connectServer :: IrcServer -> IO (IrcServer, Handle)
@ -61,3 +77,6 @@ ping = isPrefixOf "PING :"
pong :: Handle -> String -> IO () pong :: Handle -> String -> IO ()
pong handle str = sendstr handle $ "PONG " ++ (drop 5 str) pong handle str = sendstr handle $ "PONG " ++ (drop 5 str)
sendPrivmsg :: (IrcServer, Handle) -> [String] -> IO ()
sendPrivmsg (server, handle) stuff' = sendstr handle (IRC.encode $ IRC.privmsg (head stuff') (unwords . tail $ stuff'))

36
Hsbot/IRCParser.hs Normal file
View file

@ -0,0 +1,36 @@
module Hsbot.IRCParser
( IrcMsg (..)
, ircParser
) where
--import Text.Parsec
import Text.ParserCombinators.Parsec
-- |An IRC message.
data IrcMsg = IrcMsg (Maybe String) String [String] -- (Maybe first statement) cmd [chan, params/sentence]
deriving (Show)
--ircParser :: String -> IrcInput
ircParser :: String -> Either ParseError IrcMsg
ircParser str = parse pMsg "" str
pMsg = do
pfx <- optionMaybe pPrefix
cmd <- pCommand
params <- many (char ' ' >> (pLongParam <|> pShortParam))
char '\r'
eof
return $ IrcMsg pfx cmd params
pPrefix = do
char ':'
pfx <- many1 (noneOf " ")
space
return pfx
pCommand = count 3 digit <|> many1 upper
pLongParam = char ':' >> (many1 (noneOf "\r"))
pShortParam = many1 (noneOf " \r")

View file

@ -41,28 +41,30 @@ imain' modul' reboot bot = do
monitor :: (Chan IrcLine) -> Bot -> IO Bot monitor :: (Chan IrcLine) -> Bot -> IO Bot
monitor chan bot = do monitor chan bot = do
loop bot loop bot
where loop bot' = do where
input <- readChan chan loop bot' = do
input <- readChan chan :: IO IrcLine
case input of case input of
Reboot -> do Reboot -> do
putStrLn "Got reboot message, rebooting" putStrLn "Got reboot message, rebooting"
return bot' return bot'
Str str -> putStrLn ("received : " ++ str) >> loop bot' _ -> loop bot'
-- | Thread entry point for socket listeners -- | Thread entry point for socket listeners
listener :: (Chan IrcLine) -> (IrcServer, Handle) -> IO () listener :: (Chan IrcLine) -> (IrcServer, Handle) -> IO ()
listener chan (server, handle) = forever $ do listener chan (server, handle) = forever $ do
str <- hGetLine handle str <- hGetLine handle
writeChan chan (Str str) let msg = parseIrcMsg str
if ping str then pong handle str writeChan chan msg
else eval (parseIrcMsg str) eval msg
where where
eval str eval :: IrcLine -> IO ()
| (Cmd user channel (cmd, args)) <- str = do eval (Privmsg (statement, stuff')) = sendPrivmsg (server, handle) stuff'
let cmd' = tail cmd eval (Quit (ircServer, handle')) = return ()
unless (null cmd') (parseCmds user cmd' args channel) eval (Join (ircServer, handle')) = return ()
parseCmds user cmd args channel eval (Part (ircServer, handle')) = return ()
| cmd == "reboot" = writeChan chan Reboot eval (Ping (string)) = do pong handle string
| otherwise = do eval stuff' = case stuff' of
putStrLn $"Unknown command : " ++ cmd Reboot -> return ()
Nil -> return ()