lambdabot-core-5.1: Lambdabot core functionality

Safe HaskellNone
LanguageHaskell98

Lambdabot.Monad

Synopsis

Documentation

data IRCRState Source

Global read-only state.

type Callback st = IrcMessage -> ModuleT st LB () Source

type OutputFilter st = Nick -> [String] -> ModuleT st LB [String] Source

type Server st = IrcMessage -> ModuleT st LB () Source

data IRCRWState Source

Global read/write state.

Constructors

IRCRWState 

Fields

ircServerMap :: Map String (DSum ModuleID ServerRef)
 
ircPrivilegedUsers :: Set Nick
 
ircIgnoredUsers :: Set Nick
 
ircChannels :: Map ChanName String

maps channel names to topics

ircPersists :: Map String Bool

lists servers to which to reconnect on failure (one-time or always)

ircModulesByName :: Map String (Some ModuleInfo)
 
ircModulesByID :: DMap ModuleID ModuleInfo
 
ircCallbacks :: Map String (DMap ModuleID CallbackRef)
 
ircOutputFilters :: [DSum ModuleID OutputFilterRef]

Output filters, invoked from right to left

ircCommands :: Map String (DSum ModuleID CommandRef)
 

initRwState :: IRCRWState Source

Default rw state

data LB a Source

The IRC Monad. The reader transformer holds information about the connection to the IRC server.

instances Monad, Functor, MonadIO, MonadState, MonadError

class (MonadIO m, MonadBaseControl IO m, MonadConfig m, MonadLogging m, Applicative m) => MonadLB m where Source

Methods

lb :: LB a -> m a Source

Instances

inModuleNamed :: String -> LB a -> (forall st. ModuleT st LB a) -> LB a Source

Interpret an expression in the context of a module.

inModuleWithID :: ModuleID st -> LB a -> ModuleT st LB a -> LB a Source

withCommand :: String -> LB a -> (forall st. Command (ModuleT st LB) -> ModuleT st LB a) -> LB a Source

withAllModules :: (forall st. ModuleT st LB a) -> LB () Source

Interpret a function in the context of all modules