Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data Module st = Module {
- moduleSerialize :: !(Maybe (Serial st))
- moduleDefState :: !(LB st)
- moduleSticky :: !Bool
- moduleCmds :: !(ModuleT st LB [Command (ModuleT st LB)])
- moduleInit :: !(ModuleT st LB ())
- moduleExit :: !(ModuleT st LB ())
- contextual :: !(String -> Cmd (ModuleT st LB) ())
- data ModuleT st m a
- newModule :: Module st
- data LB a
- class (MonadIO m, MonadBaseControl IO m, MonadConfig m, MonadLogging m, Applicative m) => MonadLB m where
- lim80 :: Monad m => m String -> Cmd m ()
- ios80 :: MonadIO m => IO String -> Cmd m ()
- data ChanName
- mkCN :: Nick -> ChanName
- getCN :: ChanName -> Nick
- data Nick = Nick {}
- ircPrivmsg :: Nick -> String -> LB ()
- module Lambdabot.Config
- commandPrefixes :: Config [String]
- disabledCommands :: Config [String]
- editDistanceLimit :: Config Int
- enableInsults :: Config Bool
- onStartupCmds :: Config [String]
- outputDir :: Config FilePath
- dataDir :: Config FilePath
- lbVersion :: Config Version
- textWidth :: Config Int
- uncaughtExceptionHandler :: Config DIH
- replaceRootLogger :: Config Bool
- lbRootLoggerPath :: Config [String]
- consoleLogHandle :: Config Handle
- consoleLogLevel :: Config Priority
- consoleLogFormat :: Config String
- data Command m = Command {}
- data Cmd m a
- cmdNames :: Command m -> [String]
- command :: String -> Command Identity
- getTarget :: Monad m => Cmd m Nick
- getCmdName :: Monad m => Cmd m String
- say :: Monad m => String -> Cmd m ()
- withMsg :: Monad m => (forall a. Message a => a -> Cmd m t) -> Cmd m t
- readNick :: Monad m => String -> Cmd m Nick
- showNick :: Monad m => Nick -> Cmd m String
- getServer :: Monad m => Cmd m String
- getSender :: Monad m => Cmd m Nick
- getLambdabotName :: Monad m => Cmd m Nick
- module Lambdabot.State
- module Lambdabot.File
- data Serial s = Serial {
- serialize :: s -> Maybe ByteString
- deserialize :: ByteString -> Maybe s
- stdSerial :: (Show s, Read s) => Serial s
- mapSerial :: (Ord k, Show k, Show v, Read k, Read v) => Serial (Map k v)
- mapPackedSerial :: Serial (Map ByteString ByteString)
- assocListPackedSerial :: Serial [(ByteString, ByteString)]
- mapListPackedSerial :: Serial (Map ByteString [ByteString])
- readM :: (Monad m, Read a) => String -> m a
- class Packable t where
- readPacked :: ByteString -> t
- showPacked :: t -> ByteString
- readOnly :: (ByteString -> b) -> Serial b
Documentation
The Module type class.
Module | |
|
This transformer encodes the additional information a module might need to access its name or its state.
Instances
The IRC Monad. The reader transformer holds information about the connection to the IRC server.
instances Monad, Functor, MonadIO, MonadState, MonadError
Instances
Monad LB Source # | |
Functor LB Source # | |
Applicative LB Source # | |
MonadIO LB Source # | |
Defined in Lambdabot.Monad | |
MonadException LB Source # | |
MonadRandom LB Source # | |
Defined in Lambdabot.Bot getRandomPrim :: Prim t -> LB t # getRandomWord8 :: LB Word8 # getRandomWord16 :: LB Word16 # getRandomWord32 :: LB Word32 # getRandomWord64 :: LB Word64 # getRandomDouble :: LB Double # getRandomNByteInteger :: Int -> LB Integer # | |
MonadConfig LB Source # | |
MonadLogging LB Source # | |
MonadLB LB Source # | |
MonadBase IO LB Source # | |
Defined in Lambdabot.Monad | |
MonadBaseControl IO LB Source # | |
MonadState IRCRWState LB Source # | |
Defined in Lambdabot.Monad get :: LB IRCRWState # put :: IRCRWState -> LB () # state :: (IRCRWState -> (a, IRCRWState)) -> LB a # | |
type StM LB a Source # | |
Defined in Lambdabot.Monad |
class (MonadIO m, MonadBaseControl IO m, MonadConfig m, MonadLogging m, Applicative m) => MonadLB m where 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)
Send a message to a channel/user, applying all output filters
module Lambdabot.Config
commandPrefixes :: Config [String] Source #
disabledCommands :: Config [String] Source #
onStartupCmds :: Config [String] Source #
uncaughtExceptionHandler :: Config DIH Source #
lbRootLoggerPath :: Config [String] Source #
Instances
MonadTrans Cmd Source # | |
Defined in Lambdabot.Command | |
MonadTransControl Cmd Source # | |
MonadBase b m => MonadBase b (Cmd m) Source # | |
Defined in Lambdabot.Command | |
MonadBaseControl b m => MonadBaseControl b (Cmd m) Source # | |
Monad m => Monad (Cmd m) Source # | |
Functor f => Functor (Cmd f) Source # | |
Applicative f => Applicative (Cmd f) Source # | |
MonadIO m => MonadIO (Cmd m) Source # | |
Defined in Lambdabot.Command | |
MonadConfig m => MonadConfig (Cmd m) Source # | |
MonadLogging m => MonadLogging (Cmd m) Source # | |
MonadLB m => MonadLB (Cmd m) Source # | |
MonadLBState m => MonadLBState (Cmd m) Source # | |
type StT Cmd a Source # | |
Defined in Lambdabot.Command | |
type LBState (Cmd m) Source # | |
Defined in Lambdabot.State | |
type StM (Cmd m) a Source # | |
Defined in Lambdabot.Command |
module Lambdabot.State
module Lambdabot.File
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
revision 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 #
readPacked :: ByteString -> t Source #
showPacked :: t -> ByteString Source #
Instances
Packable [(ByteString, ByteString)] Source # | |
Defined in Lambdabot.Util.Serial readPacked :: ByteString -> [(ByteString, ByteString)] Source # showPacked :: [(ByteString, ByteString)] -> ByteString Source # | |
Packable (Map ByteString [ByteString]) Source # | An instance for Map Packed [Packed] uses gzip compression |
Defined in Lambdabot.Util.Serial readPacked :: ByteString -> Map ByteString [ByteString] Source # showPacked :: Map ByteString [ByteString] -> ByteString Source # | |
Packable (Map ByteString (Bool, [(String, Int)])) Source # | |
Defined in Lambdabot.Util.Serial readPacked :: ByteString -> Map ByteString (Bool, [(String, Int)]) Source # showPacked :: Map ByteString (Bool, [(String, Int)]) -> ByteString Source # | |
Packable (Map ByteString ByteString) Source # | |
Defined in Lambdabot.Util.Serial |
readOnly :: (ByteString -> b) -> Serial b Source #