{- This file is part of funbot. - - Written in 2015, 2016 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 - . -} {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Control.Concurrent.Chan (newChan) import Control.Monad.IO.Class (liftIO) import Data.Default.Class (def) import Data.Settings.Section (empty) import FunBot.Commands import FunBot.ExtHandlers (handler) import FunBot.KnownNicks import FunBot.Memos import FunBot.Settings import FunBot.Settings.Persist import FunBot.Settings.Sections import FunBot.Sources import FunBot.Types import FunBot.UserOptions import FunBot.Util (cmds) import Network.IRC.Fun.Bot (runBot) import Network.IRC.Fun.Bot.EventMatch import Network.IRC.Fun.Bot.Types (Behavior (..), EventMatchSpace (..)) import Web.Feed.Collect (newCommandQueue) import qualified Data.HashMap.Lazy as M (empty) import qualified FunBot.Config as C import qualified FunBot.IrcHandlers as H -- | Bot environment content env saveS saveM saveUO saveKN cq lq = BotEnv { webHookSourcePort = C.webListenerPort , saveSettings = saveS , saveMemos = saveM , saveUserOpts = saveUO , saveNicks = saveKN , feedErrorLogFile = C.feedErrorLogFile , feedCmdQueue = cq , loopbackQueue = lq } -- | Initial content of the bot state initialState sets ms userOpts nicks = BotState { bsSettings = sets , bsSTree = empty , bsMemos = ms , bsUserOptions = userOpts , bsKnownNicks = nicks , bsLastMsgTime = M.empty , bsPuppet = M.empty , bsPrivPuppet = Nothing } -- | Event detector specification matchers = [ matchPrefixedCommand MatchInChannel True , matchPrefixedCommandFromNames MatchInPrivate True (Right commandSet) privCmds , matchRefCommandFromSet MatchInChannel modPleasePrefix' , matchRefCommandFromNames MatchInPrivate modPleasePrefix' True privCmds , matchRef MatchInBoth , defaultMatch ] where privCmds = cmds [ "help", "info", "echo", "tell", "get", "show-opts", "enable-history" , "disable-history", "set-history-lines", "erase-opts", "show-history" , "where", "lwhere", "gwhere" ] -- | Bot behavior definition behavior :: Behavior BotEnv BotState behavior = def { handleJoin = H.handleJoin , handleMsg = H.handleMsg , handleAction = H.handleAction , handleBotMsg = H.handleBotMsg , commandSets = [commandSet] , handleNickChange = H.handleNickChange , handleNames = H.handleNames } -- | Additional events sources mkSources state = [ webListenerSource C.webErrorLogFile , feedWatcherSource C.feedErrorLogFile state , loopbackSource ] main :: IO () main = do liftIO $ putStrLn "Loading bot settings" sets <- loadBotSettings ms <- loadBotMemos uos <- loadUserOptions nicks <- loadKnownNicks saveS <- mkSaveBotSettings saveM <- mkSaveBotMemos saveUO <- mkSaveUserOptions saveKN <- mkSaveKnownNicks cq <- newCommandQueue lq <- newChan let state = initialState sets ms uos nicks runBot C.configuration matchers behavior (mkSources state) handler (env saveS saveM saveUO saveKN cq lq) state initTree