Adds error handling for line parsing and command formatting.

master
Abhinav Sarkar 2015-06-21 18:18:59 +05:30
parent fdf641d187
commit 5f7983e1f8
5 changed files with 102 additions and 59 deletions

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE FlexibleContexts, TemplateHaskell #-}
module Network.IRC.Bot module Network.IRC.Bot
( In ( In
@ -13,7 +13,7 @@ import qualified System.Log.Logger as HSL
import ClassyPrelude import ClassyPrelude
import Control.Concurrent.Lifted (threadDelay) import Control.Concurrent.Lifted (threadDelay)
import Control.Exception.Lifted (mask_, mask) import Control.Exception.Lifted (evaluate)
import Control.Monad.State.Strict (get, put, evalStateT) import Control.Monad.State.Strict (get, put, evalStateT)
import Data.Time (addUTCTime) import Data.Time (addUTCTime)
import System.IO (hIsEOF) import System.IO (hIsEOF)
@ -31,15 +31,46 @@ $(deriveLoggers "HSL" [HSL.INFO, HSL.ERROR])
data RawIn = Line !UTCTime !Text | EOS deriving (Show, Eq) data RawIn = Line !UTCTime !Text | EOS deriving (Show, Eq)
data In = Timeout | EOD | Msg !Message deriving (Show, Eq) data In = Timeout | EOD | Msg !Message deriving (Show, Eq)
formatCommand :: (Exception e) => BotConfig -> Message -> IO ([e], [Text])
formatCommand botConfig@BotConfig { .. } message =
map (second catMaybes . partitionEithers)
. forM (defaultCommandFormatter : cmdFormatters) $ \formatter ->
try . evaluate $ formatter botConfig message
parseLine :: (Exception e)
=> BotConfig -> UTCTime -> Text -> Map MessageParserId [MessagePart]
-> IO ([e], [Message], Map MessageParserId [MessagePart])
parseLine botConfig@BotConfig { .. } time line msgParts =
map mconcat . forM parsers $ \MessageParser { .. } -> do
let parserMsgParts = concat . maybeToList $ lookup msgParserId msgParts
let parserMsgPartsMap = singletonMap msgParserId parserMsgParts
eresult <- try . evaluate $ msgParser botConfig time line parserMsgParts
return $ case eresult of
Left e -> ([e], [] , parserMsgPartsMap)
Right ParseReject -> ([] , [] , parserMsgPartsMap)
Right (ParsePartial msgParts') -> ([] , [] , singletonMap msgParserId msgParts')
Right (ParseDone message msgParts') -> ([] , [message], singletonMap msgParserId msgParts')
where
parsers = defaultParsers ++ msgParsers
sendCommandLoop :: MessageChannel Message -> Bot -> IO () sendCommandLoop :: MessageChannel Message -> Bot -> IO ()
sendCommandLoop commandChan bot@Bot { .. } = do sendCommandLoop commandChan bot@Bot { .. } = do
msg@(Message _ _ cmd) <- receiveMessage commandChan msg@(Message _ _ cmd) <- receiveMessage commandChan
let mline = formatCommand botConfig msg (exs, lines_) <- formatCommand botConfig msg
handle (\(e :: SomeException) ->
errorM ("Error while writing to connection: " ++ show e) >> closeMessageChannel commandChan) $ do forM_ exs $ \(ex :: SomeException) ->
whenJust mline $ \line -> do errorM ("Error while formatting command: " ++ show cmd ++ "\nError: " ++ show ex)
TF.hprint botSocket "{}\r\n" $ TF.Only line
infoM . unpack $ "> " ++ line when (not . null $ lines_) $
handle (\(e :: SomeException) -> do
errorM ("Error while writing to connection: " ++ show e)
closeMessageChannel commandChan) $ do
forM_ lines_ $ \line -> do
TF.hprint botSocket "{}\r\n" $ TF.Only line
infoM . unpack $ "> " ++ line
commandChanClosed <- isClosedMessageChannel commandChan
when (not commandChanClosed) $
case fromMessage cmd of case fromMessage cmd of
Just QuitCmd -> closeMessageChannel commandChan Just QuitCmd -> closeMessageChannel commandChan
_ -> sendCommandLoop commandChan bot _ -> sendCommandLoop commandChan bot
@ -63,8 +94,12 @@ readMessageLoop mvBotStatus inChan Bot { .. } timeoutDelay = evalStateT loop mem
sendMessage inChan EOD >> return msgParts sendMessage inChan EOD >> return msgParts
Right Nothing -> sendMessage inChan Timeout >> return msgParts Right Nothing -> sendMessage inChan Timeout >> return msgParts
Right (Just (Line time line)) -> do Right (Just (Line time line)) -> do
let (msgs, msgParts') = parseLine botConfig time line msgParts (exs, msgs, msgParts') <- parseLine botConfig time line msgParts
forM_ exs $ \(ex :: SomeException) ->
errorM ("Error while parsing line: " ++ unpack line ++ "\nError: " ++ show ex)
forM_ msgs $ sendMessage inChan . Msg forM_ msgs $ sendMessage inChan . Msg
return msgParts' return msgParts'
Right (Just EOS) -> sendMessage inChan EOD >> return msgParts Right (Just EOS) -> sendMessage inChan EOD >> return msgParts

View File

@ -29,9 +29,9 @@ data MessagePart = MessagePart { msgPartTarget :: !Text
-- | The result of parsing a message line. -- | The result of parsing a message line.
data MessageParseResult = data MessageParseResult =
Done !Message ![MessagePart] -- ^ A fully parsed message and leftover message parts. ParseDone !Message ![MessagePart] -- ^ A fully parsed message and leftover message parts.
| Partial ![MessagePart] -- ^ A partial message with message parts received yet. | ParsePartial ![MessagePart] -- ^ A partial message with message parts received yet.
| Reject -- ^ Returned if a message line cannot be parsed by a particular parser. | ParseReject -- ^ Returned if a message line cannot be parsed by a particular parser.
deriving (Eq, Show) deriving (Eq, Show)
-- | A message parser used for parsing text lines from the server to 'Message's. -- | A message parser used for parsing text lines from the server to 'Message's.
@ -59,6 +59,7 @@ data BotConfig = BotConfig
, botPort :: !Int , botPort :: !Int
-- | The channel to join. -- | The channel to join.
, botChannel :: !Text , botChannel :: !Text
-- | Original nick of the bot.
, botOrigNick :: !Nick , botOrigNick :: !Nick
-- | Current nick of the bot. -- | Current nick of the bot.
, botNick :: !Nick , botNick :: !Nick

View File

@ -37,7 +37,7 @@ data User
data Message = Message data Message = Message
{ msgTime :: !UTCTime -- ^ The time when the message was received/sent. { msgTime :: !UTCTime -- ^ The time when the message was received/sent.
, msgLine :: !Text -- ^ The raw message. , msgLine :: !Text -- ^ The raw message.
, message :: MessageW -- ^ The details of the parsed message. , message :: !MessageW -- ^ The details of the parsed message.
} deriving (Show, Eq) } deriving (Show, Eq)
-- | The typeclass for different types of messages. -- | The typeclass for different types of messages.
@ -49,7 +49,7 @@ class (Typeable msg, Show msg, Eq msg, Ord msg) => MessageC msg where
fromMessage (MessageW msg) = cast msg fromMessage (MessageW msg) = cast msg
-- | A wrapper over all types of messages. -- | A wrapper over all types of messages.
data MessageW = forall m . MessageC m => MessageW m deriving (Typeable) data MessageW = forall m . MessageC m => MessageW !m deriving (Typeable)
instance Show MessageW where instance Show MessageW where
show (MessageW m) = show m show (MessageW m) = show m
@ -121,8 +121,11 @@ data KickMsg = KickMsg { kickUser :: !User, kickedNick :: !Nick, kickMsg :
instance MessageC KickMsg instance MessageC KickMsg
-- | A /MODE/ message received when a user's mode changes. -- | A /MODE/ message received when a user's mode changes.
data ModeMsg = ModeMsg { modeUser :: !User, modeTarget :: !Text, mode :: !Text , modeArgs :: ![Text] } data ModeMsg = ModeMsg { modeUser :: !User
deriving (Typeable, Show, Eq, Ord) , modeTarget :: !Text
, mode :: !Text
, modeArgs :: ![Text]
} deriving (Typeable, Show, Eq, Ord)
instance MessageC ModeMsg instance MessageC ModeMsg
data WhoisReplyMsg = WhoisNoSuchNick { whoisNick :: !Nick } data WhoisReplyMsg = WhoisNoSuchNick { whoisNick :: !Nick }
@ -138,8 +141,11 @@ data WhoisReplyMsg = WhoisNoSuchNick { whoisNick :: !Nick }
instance MessageC WhoisReplyMsg instance MessageC WhoisReplyMsg
-- | All other messages which are not parsed as any of the above types. -- | All other messages which are not parsed as any of the above types.
data OtherMsg = OtherMsg { msgSource :: !Text, msgCommand :: !Text, msgTarget :: !Text , msg :: !Text } data OtherMsg = OtherMsg { msgSource :: !Text
deriving (Typeable, Show, Eq, Ord) , msgCommand :: !Text
, msgTarget :: !Text
, msg :: !Text
} deriving (Typeable, Show, Eq, Ord)
instance MessageC OtherMsg instance MessageC OtherMsg

View File

@ -12,7 +12,8 @@ module Network.IRC.MessageBus
, receiveMessage , receiveMessage
, receiveMessageEither , receiveMessageEither
, closeMessageChannel , closeMessageChannel
, awaitMessageChannel ) where , awaitMessageChannel
, isClosedMessageChannel ) where
import ClassyPrelude import ClassyPrelude
@ -27,6 +28,9 @@ doLatch (Latch mv) = putMVar mv ()
awaitLatch :: Latch -> IO () awaitLatch :: Latch -> IO ()
awaitLatch (Latch mv) = void $ takeMVar mv awaitLatch (Latch mv) = void $ takeMVar mv
latched :: Latch -> IO Bool
latched (Latch mv) = map isJust . tryReadMVar $ mv
newtype MessageBus a = MessageBus (TChan a) newtype MessageBus a = MessageBus (TChan a)
newMessageBus :: IO (MessageBus a) newMessageBus :: IO (MessageBus a)
@ -62,6 +66,9 @@ closeMessageChannel (MessageChannel latch _ _) = doLatch latch
awaitMessageChannel :: MessageChannel a -> IO () awaitMessageChannel :: MessageChannel a -> IO ()
awaitMessageChannel (MessageChannel latch _ _) = awaitLatch latch awaitMessageChannel (MessageChannel latch _ _) = awaitLatch latch
isClosedMessageChannel :: MessageChannel a -> IO Bool
isClosedMessageChannel (MessageChannel latch _ _) = latched latch
receiveMessageEither :: MessageChannel a -> MessageChannel b -> IO (Either a b) receiveMessageEither :: MessageChannel a -> MessageChannel b -> IO (Either a b)
receiveMessageEither chan1 chan2 = atomically $ receiveMessageEither chan1 chan2 = atomically $
map Left (receiveMessageSTM chan1) `orElseSTM` map Right (receiveMessageSTM chan2) map Left (receiveMessageSTM chan1) `orElseSTM` map Right (receiveMessageSTM chan2)

View File

@ -1,31 +1,21 @@
module Network.IRC.Protocol (parseLine, formatCommand) where module Network.IRC.Protocol
( defaultParsers
, defaultCommandFormatter
) where
import ClassyPrelude import ClassyPrelude
import Data.Foldable (msum) import Data.Maybe (fromJust)
import Data.Maybe (fromJust) import Data.List ((!!))
import Data.List ((!!)) import Data.Text (strip)
import Data.Text (strip)
import Network.IRC.Types import Network.IRC.Types
parseLine :: BotConfig -> UTCTime -> Text -> Map MessageParserId [MessagePart]
-> ([Message], Map MessageParserId [MessagePart])
parseLine botConfig@BotConfig { .. } time line msgParts =
mconcat . flip map parsers $ \MessageParser { .. } ->
let parserMsgParts = concat . maybeToList $ lookup msgParserId msgParts
in case msgParser botConfig time line parserMsgParts of
Reject -> ([], (singletonMap msgParserId parserMsgParts))
Partial msgParts' -> ([], (singletonMap msgParserId msgParts'))
Done message msgParts' -> ([message], (singletonMap msgParserId msgParts'))
where
parsers = [pingParser, namesParser, whoisParser, lineParser] ++ msgParsers ++ [defaultParser]
pingParser :: MessageParser pingParser :: MessageParser
pingParser = MessageParser "ping" go pingParser = MessageParser "ping" go
where where
go _ time line _ go _ time line _
| "PING :" `isPrefixOf` line = Done (Message time line . toMessage . PingMsg . drop 6 $ line) [] | "PING :" `isPrefixOf` line = ParseDone (Message time line . toMessage . PingMsg . drop 6 $ line) []
| otherwise = Reject | otherwise = ParseReject
parseMsgLine :: Text -> ([Text], Text, Text, Text, Text) parseMsgLine :: Text -> ([Text], Text, Text, Text, Text)
parseMsgLine line = (splits, command, source, target, message) parseMsgLine line = (splits, command, source, target, message)
@ -40,7 +30,7 @@ lineParser :: MessageParser
lineParser = MessageParser "line" go lineParser = MessageParser "line" go
where where
go BotConfig { .. } time line _ go BotConfig { .. } time line _
| "PING :" `isPrefixOf` line = Reject | "PING :" `isPrefixOf` line = ParseReject
| otherwise = case command of | otherwise = case command of
"PONG" -> done $ toMessage $ PongMsg message "PONG" -> done $ toMessage $ PongMsg message
"JOIN" -> done $ toMessage $ JoinMsg user "JOIN" -> done $ toMessage $ JoinMsg user
@ -52,12 +42,13 @@ lineParser = MessageParser "line" go
else ModeMsg user target mode modeArgs else ModeMsg user target mode modeArgs
"NICK" -> done $ toMessage $ NickMsg user $ Nick (drop 1 target) "NICK" -> done $ toMessage $ NickMsg user $ Nick (drop 1 target)
"433" -> done $ toMessage NickInUseMsg "433" -> done $ toMessage NickInUseMsg
"PRIVMSG" | target /= botChannel -> done $ toMessage $ PrivMsg user message "PRIVMSG"
| isActionMsg -> done $ toMessage $ ActionMsg user (initDef . drop 8 $ message) | target /= botChannel -> done $ toMessage $ PrivMsg user message
| otherwise -> done $ toMessage $ ChannelMsg user message | isActionMsg -> done $ toMessage $ ActionMsg user (initDef . drop 8 $ message)
_ -> Reject | otherwise -> done $ toMessage $ ChannelMsg user message
_ -> ParseReject
where where
done = flip Done [] . Message time line done = flip ParseDone [] . Message time line
(splits, command, source, target, message) = parseMsgLine line (splits, command, source, target, message) = parseMsgLine line
quitMessage = strip . drop 1 . unwords . drop 2 $ splits quitMessage = strip . drop 1 . unwords . drop 2 $ splits
@ -72,9 +63,9 @@ defaultParser :: MessageParser
defaultParser = MessageParser "default" go defaultParser = MessageParser "default" go
where where
go _ time line _ go _ time line _
| "PING :" `isPrefixOf` line = Reject | "PING :" `isPrefixOf` line = ParseReject
| otherwise = | otherwise =
flip Done [] . Message time line $ toMessage $ OtherMsg source command target message flip ParseDone [] . Message time line $ toMessage $ OtherMsg source command target message
where where
(_, command, source, target, message) = parseMsgLine line (_, command, source, target, message) = parseMsgLine line
@ -82,15 +73,15 @@ namesParser :: MessageParser
namesParser = MessageParser "names" go namesParser = MessageParser "names" go
where where
go BotConfig { .. } time line msgParts go BotConfig { .. } time line msgParts
| "PING :" `isPrefixOf` line = Reject | "PING :" `isPrefixOf` line = ParseReject
| otherwise = case command of | otherwise = case command of
"353" -> Partial $ MessagePart target time line : msgParts "353" -> ParsePartial $ MessagePart target time line : msgParts
"366" -> let "366" -> let
(myMsgParts, otherMsgParts) = partition ((target ==) . msgPartTarget) msgParts (myMsgParts, otherMsgParts) = partition ((target ==) . msgPartTarget) msgParts
(nicks, allLines) = concat *** intercalate "\r\n" . (++ [line]) (nicks, allLines) = concat *** intercalate "\r\n" . (++ [line])
$ unzip $ map (\MessagePart { .. } -> (namesNicks msgPartLine, msgPartLine)) myMsgParts $ unzip $ map (\MessagePart { .. } -> (namesNicks msgPartLine, msgPartLine)) myMsgParts
in Done (Message time allLines . toMessage $ NamesMsg nicks) otherMsgParts in ParseDone (Message time allLines . toMessage $ NamesMsg nicks) otherMsgParts
_ -> Reject _ -> ParseReject
where where
(_, command, _ , target, _) = parseMsgLine line (_, command, _ , target, _) = parseMsgLine line
stripNickPrefix = pack . dropWhile (`elem` ("~&@%+" :: String)) . unpack stripNickPrefix = pack . dropWhile (`elem` ("~&@%+" :: String)) . unpack
@ -101,14 +92,14 @@ whoisParser :: MessageParser
whoisParser = MessageParser "whois" go whoisParser = MessageParser "whois" go
where where
go BotConfig { .. } time line msgParts go BotConfig { .. } time line msgParts
| "PING :" `isPrefixOf` line = Reject | "PING :" `isPrefixOf` line = ParseReject
| command `elem` ["401", "311", "319", "312", "317"] = | command `elem` ["401", "311", "319", "312", "317"] =
Partial $ MessagePart target time line : msgParts ParsePartial $ MessagePart target time line : msgParts
| command == "318" = let | command == "318" = let
(myMsgParts, otherMsgParts) = partition ((target ==) . msgPartTarget) msgParts (myMsgParts, otherMsgParts) = partition ((target ==) . msgPartTarget) msgParts
allLines = intercalate "\r\n" . reverse . (line :) . map msgPartLine $ myMsgParts allLines = intercalate "\r\n" . reverse . (line :) . map msgPartLine $ myMsgParts
in Done (Message time allLines . toMessage $ parse myMsgParts) otherMsgParts in ParseDone (Message time allLines . toMessage $ parse myMsgParts) otherMsgParts
| otherwise = Reject | otherwise = ParseReject
where where
(_, command, _, target, _) = parseMsgLine line (_, command, _, target, _) = parseMsgLine line
@ -125,15 +116,18 @@ whoisParser = MessageParser "whois" go
user = splits311 !! 4 user = splits311 !! 4
host = splits311 !! 5 host = splits311 !! 5
realName = drop 1 $ splits311 !! 7 realName = drop 1 $ splits311 !! 7
channels = mconcat . maybeToList . map (words . drop 1 . unwords . drop 4 . words) . lookup "319" $ partMap channels = mconcat
. maybeToList
. map (words . drop 1 . unwords . drop 4 . words)
. lookup "319"
$ partMap
splits312 = words . fromJust . lookup "312" $ partMap splits312 = words . fromJust . lookup "312" $ partMap
server = splits312 !! 4 server = splits312 !! 4
serverInfo = drop 1 $ splits312 !! 5 serverInfo = drop 1 $ splits312 !! 5
in WhoisReplyMsg nick user host realName channels server serverInfo in WhoisReplyMsg nick user host realName channels server serverInfo
formatCommand :: CommandFormatter defaultParsers :: [MessageParser]
formatCommand botConfig@BotConfig { .. } message = defaultParsers = [pingParser, namesParser, whoisParser, lineParser, defaultParser]
msum . map (\formatter -> formatter botConfig message) $ defaultCommandFormatter : cmdFormatters
defaultCommandFormatter :: CommandFormatter defaultCommandFormatter :: CommandFormatter
defaultCommandFormatter BotConfig { .. } Message { .. } defaultCommandFormatter BotConfig { .. } Message { .. }