module Network.IRC.Fun.Bot
( runBot
)
where
import Control.Concurrent (forkIO)
import Control.Concurrent.Chan
import Control.Monad (forever, liftM, void)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.RWS (ask)
import Data.List (transpose)
import Data.Maybe (catMaybes)
import Network.IRC.Fun.Bot.Internal.Event
import Network.IRC.Fun.Bot.Internal.Logger
import Network.IRC.Fun.Bot.Internal.Types
import Network.IRC.Fun.Bot.Chat (login, joinConfig, run)
import Network.IRC.Fun.Client.ChannelLogger (LogEvent, fromClientEvent)
import Network.IRC.Fun.Client.Events (hGetIrcEvents)
startBot :: Session e s ()
startBot = do
liftIO $ putStrLn "Bot: Logging in as IRC user with nickname"
login
liftIO $ putStrLn "Bot: Joining IRC channels"
joinConfig
listenToEvent :: Chan (Either (Either LogEvent Event) a)
-> EventHandler e s a
-> Session e s ()
listenToEvent chan handler = do
event <- liftIO $ readChan chan
either handleEvent handler event
listenToIrc :: [EventMatcher e s]
-> BotEnv e s
-> Chan (Either (Either LogEvent Event) a)
-> IO ()
listenToIrc ms bot chan = do
logger <-
newLogger (liftM snd $ getTime bot) (botEventLogFile $ config bot)
putStrLn "Bot: IRC event source listening to IRC events"
let match e = matchEvent ms e (config bot) (commandSets $ behavior bot)
forever $ do
ircEvents <- hGetIrcEvents $ handle bot
let botEvents = map match ircEvents
logEvents = catMaybes $ map fromClientEvent ircEvents
interleave l1 l2 = concat $ transpose [map Left l1, map Right l2]
mapM_ (logLine logger . show) botEvents
writeList2Chan chan $ map Left $ interleave logEvents botEvents
botSession :: [EventMatcher e s]
-> [EventSource e s a]
-> EventHandler e s a
-> Session e s ()
-> Session e s ()
botSession matchers sources handler actInit = do
actInit
chan <- liftIO newChan
bot <- ask
liftIO $ void $ forkIO $ listenToIrc matchers bot chan
let launch s = forkIO $ s (config bot)
(custom bot)
(writeChan chan . Right)
(writeList2Chan chan . map Right)
(newLogger $ liftM snd $ getTime bot)
liftIO $ mapM_ launch sources
startBot
liftIO $ putStrLn "Bot: Event sink listening to events"
forever $ listenToEvent chan handler
runBot :: Config
-> [EventMatcher e s]
-> Behavior e s
-> [EventSource e s a]
-> EventHandler e s a
-> e
-> s
-> Session e s ()
-> IO ()
runBot conf matchers behav sources handler env state actInit = do
putStrLn "Bot: Starting"
run conf behav env state $ botSession matchers sources handler actInit
putStrLn "Bot: Disconnected"