{-# OPTIONS -XFunctionalDependencies -XMultiParamTypeClasses #-} -- The various types used by esoteric bot module Esotericbot.EBTypes ( module Control.Monad.State , SmallBotM , Command ( .. ) , PluginCommand ( .. ) , RunnableCommand ( .. ) , IRCCommand ( .. ) , SmallBotConf ( .. ) , ChanOpSearch ( .. ) , Plugin ( .. ) , initial_op_search , initial_state ) where import GHC.Int import Control.Monad.State import Control.Concurrent.STM import Control.Concurrent import Data.Word import Data.List.Stream as L import Data.ByteString.Lazy.Char8 import qualified Data.Map as M import System.Posix.Types type SmallBotM = StateT SmallBotConf IO -- Really I'd like to use OOHaskell for these two here, but it's not cabalized :( -- A command where the plugin responding to it is not known data Command = Command { circ_user :: ByteString , circ_chan :: Maybe ByteString , circ_cmd :: ByteString } -- A command where the plugin responding to it is known ( a plugin shortcut was used ) data PluginCommand = PluginCommand { pirc_user :: ByteString , pirc_chan :: Maybe ByteString , pirc_cmd :: ByteString , plugin :: Plugin } class RunnableCommand cmd context | cmd -> context where -- Polymorphism for running commands run_command :: cmd -> context -> SmallBotM ( ) class IRCCommand cmd where -- Polymorphism for getting informataion from commands irc_user :: cmd -> ByteString irc_chan :: cmd -> Maybe ByteString irc_cmd :: cmd -> ByteString instance IRCCommand Command where irc_user = circ_user irc_cmd = circ_cmd irc_chan = circ_chan instance IRCCommand PluginCommand where irc_user = pirc_user irc_cmd = pirc_cmd irc_chan = pirc_chan data ChanOpSearch = ChanOpSearch { underway :: Bool , done :: Bool , ops :: [ ByteString ] , threads_waiting :: Int } deriving Show data SmallBotConf = SmallBotConf { plugins :: [ Plugin ] , mmem_limit :: Maybe Integer , mchildren_mem_limit :: Maybe Integer , mtime_limit :: Maybe Integer , mhard_time_limit :: Maybe Integer , moutput_limit :: Maybe Int64 -- we do more comparisons as int64, go figure , vCurrent :: TVar Integer , go :: TVar Bool , nick :: ByteString , pass :: ByteString , chans :: [ ByteString ] , server :: String -- the name of the server we connect to , chroot :: Maybe String , user :: Maybe CUid , cserver :: Maybe ByteString -- the actual server we are transferred to , listening :: M.Map ByteString ( TVar Bool ) -- the channels to which we're listening , searching :: M.Map ByteString ( TVar ChanOpSearch ) , default_child_mem_limit :: Maybe Integer , command_prefix :: ByteString -- An IRC user prefixes his command with this ByteString } instance Show SmallBotConf where show sbc = "SmallBotConf:\n" L.++ ( L.intercalate "\n" ["plugins: " L.++ ( show $ plugins sbc ) , "memlimit: " L.++ ( show $ mmem_limit sbc ) , "children_mem_limit: " L.++ ( show $ mchildren_mem_limit sbc ) , "time_limit: " L.++ ( show $ mtime_limit sbc ) , "hard_time_limit: " L.++ ( show $ mhard_time_limit sbc ) , "output_limit: " L.++ ( show $ moutput_limit sbc ) , "nick: " L.++ ( show $ nick sbc ) , "pass: " L.++ ( show $ pass sbc ) , "chans: " L.++ ( show $ chans sbc ) , "server: " L.++ server sbc , "chroot: " L.++ ( show $ chroot sbc ) , "user: " L.++ ( show $ user sbc ) , "connected server: " L.++ ( show $ cserver sbc ) , "default_child_mem_limit: " L.++ ( show $ default_child_mem_limit sbc ) , "command_prefix: " L.++ ( show $ command_prefix sbc ) ] ) initial_op_search = ChanOpSearch { underway = False , done = False , ops = [ ] , threads_waiting = 0 } initial_state = SmallBotConf { plugins = [ ] , mmem_limit = Nothing , mchildren_mem_limit = Nothing , mtime_limit = Nothing , mhard_time_limit = Nothing , moutput_limit = Nothing , nick = empty , pass = empty , chans = [ ] , server = "" , chroot = Nothing , user = Nothing , cserver = Nothing , listening = M.empty , searching = M.empty , default_child_mem_limit = Nothing , command_prefix = pack ";" } data Plugin = Plugin { cmd :: FilePath , prefix :: ByteString , input_seperator :: Maybe ByteString , memuse :: Maybe Integer , name :: ByteString , shortcut :: Maybe ByteString } deriving Show instance Eq Plugin where l1 == l2 = cmd l1 == cmd l2