module Network.IRC.Fun.Bot
( runBot
)
where
import Control.Concurrent (forkIO)
import Control.Concurrent.Chan
import Control.Monad (forever)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.RWS (ask)
import Network.IRC.Fun.Bot.Internal.Event (matchEvent, handleEvent)
import Network.IRC.Fun.Bot.Internal.Types
import Network.IRC.Fun.Bot.Chat (login, joinConfig, run)
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 Event a) -> EventHandler e s a -> Session e s ()
listenToEvent chan handler = do
event <- liftIO $ readChan chan
either handleEvent handler event
listenToIrc :: BotEnv e s -> Chan (Either Event a) -> IO ()
listenToIrc bot chan = do
putStrLn "Bot: IRC event source listening to IRC events"
forever $ do
ircEvents <- hGetIrcEvents $ handle bot
let match e = matchEvent e (config bot) (commandSets $ behavior bot)
botEvents = map match ircEvents
mapM_ print botEvents
writeList2Chan chan $ map Left botEvents
botSession :: [EventSource e s a] -> EventHandler e s a -> Session e s ()
botSession sources handler = do
chan <- liftIO newChan
bot <- ask
liftIO $ forkIO $ listenToIrc bot chan
let launch s = forkIO $ s (config bot)
(custom bot)
(writeChan chan . Right)
(writeList2Chan chan . map Right)
liftIO $ mapM_ launch sources
startBot
liftIO $ putStrLn "Bot: Event sink listening to events"
forever $ listenToEvent chan handler
runBot :: Config
-> Behavior e s
-> [EventSource e s a]
-> EventHandler e s a
-> e
-> s
-> IO ()
runBot conf behavior sources handler env state = do
putStrLn "Bot: Starting"
run conf behavior env state $ botSession sources handler
putStrLn "Bot: Disconnected"