lambdabot-core-5.0: Lambdabot core functionality

Safe HaskellNone
LanguageHaskell98

Lambdabot.Plugin

Synopsis

Documentation

data Module st Source

The Module type class.

Constructors

Module 

Fields

moduleSerialize :: !(Maybe (Serial st))

If the module wants its state to be saved, this function should return a Serial.

The default implementation returns Nothing.

moduleDefState :: !(LB st)

If the module maintains state, this method specifies the default state (for example in case the state can't be read from a state).

The default implementation returns an error and assumes the state is never accessed.

moduleSticky :: !Bool

Is the module sticky? Sticky modules (as well as static ones) can't be unloaded. By default, modules are not sticky.

moduleCmds :: !(ModuleT st LB [Command (ModuleT st LB)])

The commands the module listenes to.

moduleInit :: !(ModuleT st LB ())

Initialize the module. The default implementation does nothing.

moduleExit :: !(ModuleT st LB ())

Finalize the module. The default implementation does nothing.

contextual :: !(String -> Cmd (ModuleT st LB) ())

Process contextual input. A plugin that implements contextual is able to respond to text not part of a normal command.

data ModuleT st m a Source

This transformer encodes the additional information a module might need to access its name or its state.

Instances

bindModule0 :: ModuleT mod LB a -> ModuleT mod LB (LB a) Source

bind an action to the current module so it can be run from the plain LB monad.

bindModule1 :: (a -> ModuleT mod LB b) -> ModuleT mod LB (a -> LB b) Source

variant of bindModule0 for monad actions with one argument

bindModule2 :: (a -> b -> ModuleT mod LB c) -> ModuleT mod LB (a -> b -> LB c) Source

variant of bindModule0 for monad actions with two arguments

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

MonadLB LB 
MonadLB m => MonadLB (Cmd m) 
MonadLB m => MonadLB (ModuleT st m) 

lim80 :: Monad m => m String -> Cmd m () Source

ios80 :: MonadIO m => IO String -> Cmd m () Source

convenience, similar to ios but also cut output to channel to 80 characters usage: process _ _ to _ s = ios80 to (plugs s)

data Nick Source

The type of nicknames isolated from a message.

Constructors

Nick 

Fields

nTag :: !String

The tag of the server this nick is on

nName :: !String

The server-specific nickname of this nick

Instances

ircPrivmsg Source

Arguments

:: Nick

The channel/user.

-> String

The message.

-> LB () 

Send a message to a channel/user. If the message is too long, the rest of it is saved in the (global) more-state.

data Serial s Source

Constructors

Serial 

stdSerial :: (Show s, Read s) => Serial s Source

Default `instance' for a Serial

mapSerial :: (Ord k, Show k, Show v, Read k, Read v) => Serial (Map k v) Source

Serializes a Map type if both the key and the value are instances of Read and Show. The serialization is done by converting the map to and from lists. Results are saved line-wise, for better editing and revison control.

readM :: (Monad m, Read a) => String -> m a Source

readM behaves like read, but catches failure in a monad. this allocates a 20-30 M on startup...

class Packable t where Source

Instances

Packable [(ByteString, ByteString)] 
Packable (Map ByteString [ByteString])

An instance for Map Packed [Packed] uses gzip compression

Packable (Map ByteString (Bool, [(String, Int)])) 
Packable (Map ByteString ByteString)