{- This file is part of irc-fun-bot. - - Written in 2015 by fr33domlover . - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} -- | This module allows you to define bot event handlers and commands, and then -- just run event source and sink threads in your @main@ function and let them -- handle all the details. 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) -- Get the bot ready for listening to IRC messages. startBot :: Session e s () startBot = do liftIO $ putStrLn "Bot: Logging in as IRC user with nickname" login liftIO $ putStrLn "Bot: Joining IRC channels" joinConfig -- Wait for an IRC event, then handle it according to bot behavior definition. 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 -- Collect IRC events from the server and push into a 'Chan' for the main -- thread to handle. 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 -- Connect, login, join. Then listen to events and handle them, forever. 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 -- | Start the bot and run its event loop. The bot will listen to messages from -- the IRC server and other provided sources, and will respond according to the -- behavior definitions. runBot :: Config -- ^ IRC connection configuration -> [EventMatcher e s] -- ^ Event detection (high-to-low priority) -> Behavior e s -- ^ Behavior definition for IRC events -> [EventSource e s a] -- ^ Additional event source threads to run -> EventHandler e s a -- ^ Handler for events coming from those sources -> e -- ^ Custom bot environment (read-only state) -> s -- ^ Initial state to hold in the background -> Session e s () -- ^ Initialization action to run at the very -- beginning of the session -> 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"