{- This file is part of irc-fun-bot. - - 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 GeneralizedNewtypeDeriving #-} module Network.IRC.Fun.Bot.Internal.Types ( Config () , cfgConnection , cfgChannels , cfgLogDir , cfgStateRepo , cfgStateFile , cfgSaveInterval , cfgIrcEventLogFile , cfgIrcErrorLogFile , cfgExtEventLogFile , cfgExtErrorLogFile , cfgMaxMsgChars , cfgLagCheck , cfgLagMax , cfgMaxMsgCount , cfgMsgDelay , MessageSource (..) , Failure (..) , CommandName (..) , Command (..) , CommandSet (..) , IrcMsg (..) , BotEnv (..) , MsgCountEntry (..) , ChanState (..) , ChanInfo (..) , HistoryLine (..) , BotState (..) , Session (..) , ChannelPrivacy (..) , Privilege (..) , Event (..) , EventMatcher , EventMatchSpace (..) , Behavior (..) , Logger (..) , Msg (..) , EventSource , EventHandler ) where import Control.Applicative (Applicative) import Control.Concurrent.Chan (Chan) import Control.Monad.Fix (MonadFix) import Control.Monad.IO.Class (MonadIO) import Control.Monad.Trans.RWS (RWST) import Data.CaseInsensitive (CI) import Data.Default.Class import Data.HashMap.Lazy (HashMap) import Data.HashSet (HashSet) import Data.Int (Int64) import Data.Sequence (Seq) import Data.Text (Text, pack) import Data.Time.Clock (UTCTime) import Data.Time.Interval (TimeInterval, time) import Data.Time.Units import Network.IRC.Fun.Client.ChannelLogger (LogEvent) import Network.IRC.Fun.Client.IO (ConnConfig, Connection) import Network.IRC.Fun.Client.NickTracker (NetworkTracker) import Network.IRC.Fun.Types hiding (Command) import System.Log.FastLogger (LoggerSet) import qualified Network.IRC.Fun.Client.ChannelLogger as L (Logger) import qualified Network.IRC.Fun.Client.Events as C (Event) -- | Configuration for the bot connection to IRC. -- -- Get a default bot configuration using 'def', and use record syntax to -- override just the fields you need. It allows adding a field without breaking -- backwards compatibility. data Config = Config { -- | Connection details, including nickname and optional password cfgConnection :: ConnConfig -- | The list of channels for the bot to join is generally set in the -- state file, but when the bot launches it joins both the channels -- listed there and the ones listed here. This list is intended to be -- used as hard-coded backup, i.e. the bot will always join these -- channels regardless of what the state file says. , cfgChannels :: [Channel] -- | Directory path under which IRC log files will be placed. Relative to -- the bot process working directory, or absolute. , cfgLogDir :: FilePath -- | Directory path for the state file. This enables Git commits of the -- state file. A relative (to the bot process working dir) or absolute -- path to the Git repository. You must create the directory yourself if -- it doesn't exist, but repo will be auto-created for you if needed. , cfgStateRepo :: Maybe FilePath -- | Filename into the bot state managed by this library will be stored. -- The custom part of the state isn't handled. If 'stateDir' is -- 'Nothing', this is a path relative to the bot process working -- directory, or absolute. Otherwise, it's relative to the 'stateDir'. , cfgStateFile :: FilePath -- | Minimal time interval between state saves. For example, to say -- \"don't write state to file more than once per three seconds\", set -- this field to 3 seconds, i.e. @time (3 :: Second)@. , cfgSaveInterval :: TimeInterval -- | Filename for the bot's main event log, i.e. produced by the IRC -- event source. , cfgIrcEventLogFile :: Maybe FilePath -- | Filename for writing error messages generated by invalid IRC lines -- or errors in their analysis or in event detection. Useful for -- debugging. , cfgIrcErrorLogFile :: Maybe FilePath -- | Filename for the bot's external handler event log. , cfgExtEventLogFile :: Maybe FilePath -- | Filename for writing error messages generated by invalid external -- events or errors in their analysis or handling. Useful for debugging. , cfgExtErrorLogFile :: Maybe FilePath -- | Maximal number of characters in a message the bot can send to a user -- or a channel. Longer messages will be split. 'Nothing' means no limit, -- i.e. let the IRC server truncate long messages. This limit applies to -- 'sendToUser' and 'sendToChannel' and all the functions which use them. -- A safe default if you want to set a limit is 400. , cfgMaxMsgChars :: Maybe Int -- | Time interval for sending PINGs to the server, to make sure the -- connection is alive. 'Nothing' means no PINGs sent. , cfgLagCheck :: Maybe TimeInterval -- | Maximal lag time allowed before the bot quits. , cfgLagMax :: TimeInterval -- | Maximal number of messages to count per channel in the message -- counter. Possibly a bit more will be counted, in cases it doesn't -- require more memory anyway. If a user misses more than that number N, -- they will simply be notified \"you missed at least N messages!\". -- -- TODO actually right now this is the maximal length of the per-channel -- log, which includes messages, joins and parts. It's just a tool to -- limit memory usage, nothing more. , cfgMaxMsgCount :: Int -- | IRC messages can be sent to users or channels either instantly, or -- through a dedicated sender thread. That thread creates a delay -- between messages, to avoid flooding, since that may result with the -- server blocking some of the messages. This option sets the time to -- wait between messages. , cfgMsgDelay :: TimeInterval } deriving Show instance Default Config where def = Config { cfgConnection = def , cfgChannels = [Channel $ pack "#freepost-bot-test"] , cfgLogDir = "state/chanlogs" , cfgStateRepo = Nothing , cfgStateFile = "state/state.json" , cfgSaveInterval = time (3 :: Second) , cfgIrcEventLogFile = Nothing , cfgIrcErrorLogFile = Nothing , cfgExtEventLogFile = Nothing , cfgExtErrorLogFile = Nothing , cfgMaxMsgChars = Nothing , cfgLagCheck = Just $ time (1 :: Minute) , cfgLagMax = time (5 :: Minute) , cfgMaxMsgCount = 1000 , cfgMsgDelay = time (100 :: Millisecond) } -- | A message for the bot can come privately or in a channel by a given user. data MessageSource = SrcChannel Channel Nickname | SrcUser Nickname deriving (Eq, Show) -- | Describes wrong usage of a bot command. data Failure -- | The number of arguments given is wrong = WrongNumArgs -- | \ arguments were given, instead of \ | WrongNumArgsN (Maybe Int) (Maybe Int) -- | At least one of the arguments is invalid | InvalidArgs -- | Argument in position \ and value \ -- invalid | InvalidArg (Maybe Int) (Maybe Text) -- | Some other error, with a given description | OtherFail Text deriving (Eq, Show) -- | A bot command name. newtype CommandName = CommandName { unCommandName :: CI Text } deriving (Eq, Show) -- | A bot command, triggered by a message sent to an IRC channel the bot has -- joined. -- -- The type parameter @e@ is the type of environment, i.e. real-only state. The -- type parameter @s@ is the type of the writable state the bot holds. For -- example, maybe you want your bot to keep a list of to-do items and manage it -- using bot commands. The bot state is where you store the to-do list. data Command e s = Command { -- | The command's name string, e.g. @"echo"@. More than one name is -- allowed per command, so that localized names and shortcuts can be made -- available. -- -- The first name in the list is considered the /primary name/. When one -- name is shown, e.g. in help messages, it will be the primary name. cmdNames :: [CommandName] -- | What to do in response to the command being triggered by an IRC -- user. The bot can send an IRC message back to the channel, or modify -- its state, or both. -- -- The returned value is in the 'Session' monad (it is really 'RWST' -- behind the scenes), which allows the bot to access the configuration -- and bot state, store and load data from files, communicate through the -- network (e.g. download RSS feeds) and more. -- -- Parameters: -- -- (1) Channel in which the command was triggered, if any -- (2) Nickname of user who triggered the command -- (3) Command parameters given -- (4) Action for sending a message back to the sender, same as using -- @sendBack@ with the channel and nickname , cmdRespond :: Maybe Channel -> Nickname -> [Text] -> (MsgContent -> Session e s ()) -> Session e s () -- | Help string for the command, explaining it purpose, its parameters -- and its usage. May contain newlines. , cmdHelp :: Text -- | Usage examples. Each item should be a single command invocation, -- single line, no newlines, no command prefix. For instance, -- @\"tell joe How are you?\"@ is an example for a hypothetical @tell@ -- command. , cmdExamples :: [Text] } -- | The bot recognizes commands by picking IRC channel messages which begin -- with a special character, the command prefix. It's possible to have several -- prefixes, maybe give each its own role or meaning. A command set is a set of -- commands which share a prefix. -- -- A command can be in more than one set. -- -- Common prefixes are @'!', '\@', '>', ':'@. data CommandSet e s = CommandSet { csetPrefix :: Char , csetCommands :: [Command e s] } -- An IRC message to send to a user or a channel. data IrcMsg = IrcMsg { msgRecip :: Either Nickname Channel , msgLines :: [MsgContent] , msgNotice :: Bool } deriving (Show) -- Read-only bot environment. -- -- The full environment is exposed to commands, which is both power and -- responsibility. For example, uncareful use of the handle (this is a handle -- to the TCP socket) could cause parsing issues or disconnection. The 'Config' -- contains the bot's nickname password, which shouldn't be shared publicly. -- -- At the same time, you can send any custom message you wish to the IRC -- server, even if the libraries don't support it directly, or you could use -- the password to automatically re-identify in case of any problem with -- NickServ. And so on. data BotEnv e s = BotEnv { beConfig :: Config , beBehavior :: Behavior e s , beConn :: Connection , beGetTime :: IO (UTCTime, Text) -- An 'IO' action which reads a periodically updated counter of the -- number of minutes since the epoch. , beGetMinute :: IO Int64 , beSaveState :: BotState s -> IO () , beMsgQueue :: Chan IrcMsg , beCustom :: e } -- | Message counter log entry. data MsgCountEntry -- | Number of messages sent in a channel = MsgCountMsgs Int -- | User joined the channel | MsgCountJoin Nickname UTCTime -- | User left the channel | MsgCountPart Nickname UTCTime -- Per-channel modifiable state data ChanState = ChanState { -- Whether user-in-channel tracking is enabled for this channel csTracking :: Bool -- Whether message counting is enabled for this channel , csCounting :: Bool -- An optional channel-activity-to-text-file logger , csLogger :: Maybe L.Logger -- Maximal number of channel message history lines to remember , csHistoryLines :: Int -- Whether to send a response when an invalid command is attempted. If -- not, then simply ignore the attempt. , csDefResponse :: Bool } data ChanInfo = ChanInfo { -- | Whether user-in-channel tracking is enabled for this channel ciTrack :: Bool -- | Whether message counting is enabled for this channel , ciCount :: Bool -- | Whether logging-to-file is enabled for this channel , ciLog :: Bool -- | Maximal number of channel message history lines to remember , ciHistoryLines :: Int -- | Whether to respond to nonexistent command attempts , ciDefResponse :: Bool } -- | A message sent previously by an IRC user into a channel. data HistoryLine = HistoryLine { hlTime :: Text , hlNick :: Nickname , hlMessage :: MsgContent , hlAction :: Bool , hlMinute :: Int64 } -- Readable and writable bot state. Contains internal state used by this -- library, and public state managed by the bot's behavior logic. data BotState s = BotState { -- Keeps track of which users are in which channels bsTracker :: NetworkTracker -- Per-channel persistent state , bsChannels :: HashMap Channel ChanState -- Channels of which the bot is currently a member , bsCurrChans :: HashSet Channel -- Channels the bot should join when it launches , bsSelChans :: HashSet Channel -- Per-channel last messages , bsHistory :: HashMap Channel (Seq HistoryLine) -- Per-channel message counter log , bsMsgCountLog :: HashMap Channel (Seq MsgCountEntry) -- Custom state , bsPublic :: s } -- | Bot monad. newtype Session e s a = Session { unSession :: RWST (BotEnv e s) () (BotState s) IO a } deriving (Functor, Applicative, Monad, MonadFix, MonadIO) -- An event triggered by an IRC message sent from the server. data Event -- | A ping was sent to the bot. The parameters contain the arguments -- passed, which should be passed in the Pong. = Ping Hostname (Maybe Hostname) -- | Users (2nd parameter) have been kicked from a channel (1st parameter) -- for a given reason (3rd parameter). | Kick Channel [Nickname] (Maybe Comment) -- | A user (2nd parameter) joined a channel (1st parameter). | Join Channel Nickname -- | A user (2nd parameter) left a channel (1st parameter), 3rd=reason. | Part Channel Nickname (Maybe Comment) -- | User, reason. | Quit Nickname (Maybe Comment) -- | Message (3rd parameter) sent in a channel (1st parameter) by a user -- with the given nickname (2nd parameter). The last parameter says whether -- the bot's nick is mentioned in the message. | Message Channel Nickname MsgContent Bool -- | Like 'Message', but it's a pseudo action (/me). | Action Channel Nickname MsgContent Bool -- | Like 'Message', but this is a notice. The bot shouldn't send a -- response (but it can modify its state etc.). First parameter: Just -- channel, or Nothing. The latter means a private message. | Notice (Maybe Channel) Nickname MsgContent -- | Message referring to the bot sent in a channel. The message begins -- with the bot's nick, followed by a colon or a comma. For example, if the -- message was \"funbot, hello!\" then the 3rd parameter will be -- \"hello!\". The parameters are: Channel, nickname, stripped message, -- full message including the reference. | BotMessage Channel Nickname MsgContent MsgContent -- | A bot command, which is a message with a special prefix, was sent to -- a channel or privately to the bot. Parameters: Source, prefix character, -- command name, command arguments. | BotCommand MessageSource (Maybe Char) CommandName [Text] -- | A private message sent specifically to the bot, from a user with the -- given nickname (1st parameter) and with the given content (2nd -- parameter). | PersonalMessage Nickname MsgContent -- | Like 'PersonalMessage', but it's a pseudo action (/me). | PersonalAction Nickname MsgContent -- | Old nick, new nick. | NickChange Nickname Nickname -- | Channel, nickname, topic | TopicChange Channel Nickname ChannelTopic -- | The server sent a list of nicknames present in a channel. Parameters: -- Channel privacy mode, channel name, list of users. Each list item is a -- pair of a user privilege level in the channel, and the user's nickname. | Names Channel ChannelPrivacy [(Privilege, Nickname)] -- | Unrecognized or unimplemented event. The parameter contains (possibly -- empty) input. | OtherEvent Text deriving Show -- | Tries to match a client event to a bot event. type EventMatcher e s = C.Event -> Config -> [CommandSet e s] -> Maybe Event -- | Where an event matcher applies. data EventMatchSpace = MatchInChannel | MatchInPrivate | MatchInBoth -- | Bot behavior definition. data Behavior e s = Behavior { handleJoin :: Channel -> Nickname -> Session e s () , handlePart :: Channel -> Nickname -> Maybe Comment -> Session e s () , handleQuit :: Nickname -> Maybe Comment -> Session e s () , handleMsg :: Channel -> Nickname -> MsgContent -> Bool -> Session e s () , handleAction :: Channel -> Nickname -> MsgContent -> Bool -> Session e s () , handleBotMsg :: Channel -> Nickname -> MsgContent -> MsgContent -> Session e s () , commandSets :: [CommandSet e s] , handlePersonalMsg :: Nickname -> MsgContent -> Session e s () , handlePersonalAction :: Nickname -> MsgContent -> Session e s () , handleNickChange :: Nickname -> Nickname -> Session e s () , handleTopicChange :: Channel -> Nickname -> ChannelTopic -> Session e s () -- | Handle a channel member list received. Parameters: -- -- (1) Channel name -- (2) Channel privacy -- (3) List of channel members: their privilege level in the channel and -- their nicknames , handleNames :: Channel -> ChannelPrivacy -> [(Privilege, Nickname)] -> Session e s () } instance Default (Behavior e s) where def = Behavior { handleJoin = \ _ _ -> return () , handlePart = \ _ _ _ -> return () , handleQuit = \ _ _ -> return () , handleMsg = \ _ _ _ _ -> return () , handleAction = \ _ _ _ _ -> return () , handleBotMsg = \ _ _ _ _ -> return () , commandSets = [] , handlePersonalMsg = \ _ _ -> return () , handlePersonalAction = \ _ _ -> return () , handleNickChange = \ _ _ -> return () , handleTopicChange = \ _ _ _ -> return () , handleNames = \ _ _ _ -> return () } data Logger = Logger { loggerSet :: LoggerSet , loggerGetTime :: IO Text } -- An event passed to the main thread (event handler) from other threads. data Msg a = MsgLogEvent LogEvent | MsgHistoryEvent Nickname Channel MsgContent Bool | MsgCountLogMsg Channel | MsgCountLogJoin Nickname Channel | MsgCountLogPart Nickname Channel | MsgCountLogQuit Nickname | MsgBotEvent Event | MsgExtEvent a | MsgQuit -- | An 'IO' action, possibly running forever, which produces events for the -- bot to process. These event sources are run by the bot in dedicated threads. -- -- Type parameters: -- -- * @e@ - custom bot environment type -- * @s@ - custom bot state type -- * @a@ - event type type EventSource e s a = Config -- ^ The bot configuration. The event source may find this useful. -> e -- ^ The bot's custom environment. The event source may find this useful. -> (a -> IO ()) -- ^ A non-blocking 'IO' action which sends a given event to the -- processing queue. -> ([a] -> IO ()) -- ^ A non-blocking 'IO' action which sends a given list of events to the -- processing queue. -> (FilePath -> IO Logger) -- ^ An 'IO' action which creates a logger with a given target filename. -- An event source can use it to log events, errors, debug into, etc. into -- files efficiently. -> IO () -- | A bot session action which reacts to a single event which came from an -- 'EventSource'. -- -- Type parameters: -- -- * @e@ - custom bot environment type -- * @s@ - custom bot state type -- * @a@ - event type -- -- Parameters: -- -- (1) Error logging function -- (2) Event logging function -- (3) The event -- -- Note that logging can be turned on and off using the bot config, i.e. the -- handler function can safely use logging and the messages will simply and -- safely be discarded when logging is off. type EventHandler e s a = (Text -> Session e s ()) -> (Text -> Session e s ()) -> a -> Session e s ()