Added reconnected/rejoin support in case of disconnects/kick/kickban

master
Abhinav Sarkar 2014-05-04 07:03:23 +05:30
parent 17c3873ef8
commit 4776e0843d
4 changed files with 80 additions and 37 deletions

View File

@ -2,35 +2,57 @@
module Network.IRC.Client(run) where module Network.IRC.Client(run) where
import qualified Control.Exception as E import Control.Exception
import Control.Concurrent import Control.Concurrent
import Control.Monad.Reader import Control.Monad.Reader
import Network import Network
import Prelude hiding (log)
import System.IO import System.IO
import System.Time import System.Time
import System.Timeout
import Text.Printf import Text.Printf
import Network.IRC.Handlers import Network.IRC.Handlers
import Network.IRC.Protocol import Network.IRC.Protocol
import Network.IRC.Types import Network.IRC.Types
data Status = Connected | Disconnected | Joined | Kicked | Errored
deriving (Show, Eq)
oneSec = 1000000
io = liftIO io = liftIO
log msg = putStrLn $ "** " ++ msg
sendCommand :: Bot -> Command -> IO () sendCommand :: Bot -> Command -> IO ()
sendCommand Bot{ .. } reply = do sendCommand Bot{ .. } reply = do
let line = lineFromCommand botConfig reply let line = lineFromCommand botConfig reply
hPrintf socket "%s\r\n" line >> printf "> %s\n" line hPrintf socket "%s\r\n" line >> printf "> %s\n" line
listen :: IRC () listen :: Status -> IRC Status
listen = forever $ do listen status = do
bot@Bot{ .. } <- ask bot@Bot{ .. } <- ask
let nick = botNick botConfig
line <- fmap init $ io $ hGetLine socket when (status == Kicked) $
io $ threadDelay (5 * oneSec) >> sendCommand bot JoinCmd
mLine <- io . timeout (oneSec * botTimeout botConfig) . hGetLine $ socket
case mLine of
Nothing -> return Disconnected
Just l -> do
let line = init l
time <- io getClockTime time <- io getClockTime
io $ printf "[%s] %s\n" (show time) line io $ printf "[%s] %s\n" (show time) line
io $ forkIO $ case msgFromLine botConfig time line of let message = msgFromLine botConfig time line
nStatus <- io $ case message of
JoinMsg { .. } | userNick user == nick -> log "Joined" >> return Joined
KickMsg { .. } -> log "Kicked" >> return Kicked
_ -> do
forkIO $ case message of
Ping { .. } -> sendCommand bot $ Pong msg Ping { .. } -> sendCommand bot $ Pong msg
ModeMsg { user = Self, .. } -> sendCommand bot JoinCmd ModeMsg { user = Self, .. } -> sendCommand bot JoinCmd
msg -> forM_ (handlers botConfig) $ \handler -> do msg -> forM_ (handlers botConfig) $ \handler -> do
@ -38,26 +60,44 @@ listen = forever $ do
case cmd of case cmd of
Nothing -> return () Nothing -> return ()
Just cmd -> sendCommand bot cmd Just cmd -> sendCommand bot cmd
return status
listen nStatus
connect :: BotConfig -> IO Bot connect :: BotConfig -> IO Bot
connect botConfig@BotConfig{ .. } = do connect botConfig@BotConfig{ .. } = do
putStrLn "** Connecting ..." log "Connecting ..."
handle <- connectTo server (PortNumber (fromIntegral port)) handle <- connectToWithRetry
hSetBuffering handle LineBuffering hSetBuffering handle LineBuffering
hSetBuffering stdout LineBuffering hSetBuffering stdout LineBuffering
putStrLn "** Connected" log "Connected"
return $ Bot botConfig handle return $ Bot botConfig handle
where
connectToWithRetry = connectTo server (PortNumber (fromIntegral port))
`catch` (\(e :: SomeException) -> do
log ("Error: " ++ show e ++ ". Waiting.")
threadDelay (5 * oneSec)
connectToWithRetry)
disconnect :: Bot -> IO () disconnect :: Bot -> IO ()
disconnect bot = do disconnect bot = do
putStrLn "** Disconnecting ..." log "Disconnecting ..."
hClose . socket $ bot hClose . socket $ bot
putStrLn "** Disconnected" log "Disconnected"
run :: BotConfig -> IO () run :: BotConfig -> IO ()
run botConfig = E.bracket (connect botConfig) disconnect $ \bot -> run botConfig = withSocketsDo $ do
E.catch (run_ bot) (\(e :: E.SomeException) -> putStrLn $ "Exception! " ++ show e) status <- run_
case status of
Disconnected -> log "Connection timedout" >> run botConfig
Errored -> return ()
where where
run_ bot = do run_ = bracket (connect botConfig) disconnect $ \bot ->
sendCommand bot NickCmd >> sendCommand bot UserCmd go bot `catch` \(e :: SomeException) -> do
runReaderT listen bot log $ "Exception! " ++ show e
return Errored
go bot = do
sendCommand bot NickCmd
sendCommand bot UserCmd
runReaderT (listen Connected) bot

View File

@ -19,5 +19,4 @@ main = do
if length args < 4 if length args < 4
then putStrLn ("Usage: " ++ prog ++ " <server> <port> <channel> <nick>") >> exitFailure then putStrLn ("Usage: " ++ prog ++ " <server> <port> <channel> <nick>") >> exitFailure
else run $ BotConfig server port channel botNick handlers else run $ BotConfig server port channel botNick 120 handlers

View File

@ -15,6 +15,7 @@ msgFromLine (BotConfig { .. }) time line
"JOIN" -> JoinMsg time user "JOIN" -> JoinMsg time user
"QUIT" -> QuitMsg time user message "QUIT" -> QuitMsg time user message
"PART" -> PartMsg time user message "PART" -> PartMsg time user message
"KICK" -> KickMsg time user kickReason
"MODE" -> if source == botNick "MODE" -> if source == botNick
then ModeMsg time Self target message [] then ModeMsg time Self target message []
else ModeMsg time user target mode modeArgs else ModeMsg time user target mode modeArgs
@ -34,6 +35,7 @@ msgFromLine (BotConfig { .. }) time line
user = let u = splitWhen (== '!') source in User (u !! 0) (u !! 1) user = let u = splitWhen (== '!') source in User (u !! 0) (u !! 1)
mode = splits !! 3 mode = splits !! 3
modeArgs = drop 4 splits modeArgs = drop 4 splits
kickReason = drop 1 . unwords . drop 4 $ splits
lineFromCommand :: BotConfig -> Command -> String lineFromCommand :: BotConfig -> Command -> String
lineFromCommand (BotConfig { .. }) reply = case reply of lineFromCommand (BotConfig { .. }) reply = case reply of

View File

@ -22,6 +22,7 @@ data Message =
| NickMsg { time :: ClockTime, user :: User, nick :: String } | NickMsg { time :: ClockTime, user :: User, nick :: String }
| QuitMsg { time :: ClockTime, user :: User, msg :: String } | QuitMsg { time :: ClockTime, user :: User, msg :: String }
| PartMsg { time :: ClockTime, user :: User, msg :: String } | PartMsg { time :: ClockTime, user :: User, msg :: String }
| KickMsg { time :: ClockTime, user :: User, msg :: String }
| OtherMsg { time :: ClockTime, source :: String, command :: String | OtherMsg { time :: ClockTime, source :: String, command :: String
, target :: String, msg :: String } , target :: String, msg :: String }
deriving (Show, Eq) deriving (Show, Eq)
@ -39,6 +40,7 @@ data BotConfig = BotConfig { server :: String
, port :: Int , port :: Int
, channel :: String , channel :: String
, botNick :: String , botNick :: String
, botTimeout :: Int
, handlers :: [HandlerName] } , handlers :: [HandlerName] }
deriving (Show, Eq) deriving (Show, Eq)
data Bot = Bot { botConfig :: BotConfig, socket :: Handle } deriving (Show, Eq) data Bot = Bot { botConfig :: BotConfig, socket :: Handle } deriving (Show, Eq)