Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data IRCRState
- initRoState :: [DSum Config Identity] -> IO IRCRState
- reportInitDone :: LB ()
- waitForInit :: MonadLB m => m ()
- waitForQuit :: MonadLB m => m ()
- type Callback st = IrcMessage -> ModuleT st LB ()
- type OutputFilter st = Nick -> [String] -> ModuleT st LB [String]
- type Server st = IrcMessage -> ModuleT st LB ()
- data IRCRWState = IRCRWState {
- ircServerMap :: Map String (DSum ModuleID ServerRef)
- ircPrivilegedUsers :: Set Nick
- ircIgnoredUsers :: Set Nick
- ircChannels :: Map ChanName String
- ircPersists :: Map String Bool
- ircModulesByName :: Map String (Some ModuleInfo)
- ircModulesByID :: DMap ModuleID ModuleInfo
- ircCallbacks :: Map String (DMap ModuleID CallbackRef)
- ircOutputFilters :: [DSum ModuleID OutputFilterRef]
- ircCommands :: Map String (DSum ModuleID CommandRef)
- initRwState :: IRCRWState
- data LB a
- runLB :: LB a -> (IRCRState, IORef IRCRWState) -> IO a
- class (MonadIO m, MonadBaseControl IO m, MonadConfig m, MonadLogging m, Applicative m, MonadFail m) => MonadLB m where
- registerModule :: String -> Module st -> st -> LB (ModuleInfo st)
- registerCommands :: [Command (ModuleT st LB)] -> ModuleT st LB ()
- registerCallback :: String -> Callback st -> ModuleT st LB ()
- registerOutputFilter :: OutputFilter st -> ModuleT st LB ()
- unregisterModule :: String -> LB ()
- registerServer :: String -> Server st -> ModuleT st LB ()
- unregisterServer :: String -> ModuleT mod LB ()
- send :: IrcMessage -> LB ()
- received :: IrcMessage -> LB ()
- applyOutputFilters :: Nick -> String -> LB [String]
- inModuleNamed :: String -> LB a -> (forall st. ModuleT st LB a) -> LB a
- inModuleWithID :: ModuleID st -> LB a -> ModuleT st LB a -> LB a
- withCommand :: String -> LB a -> (forall st. Command (ModuleT st LB) -> ModuleT st LB a) -> LB a
- listModules :: LB [String]
- withAllModules :: (forall st. ModuleT st LB a) -> LB ()
Documentation
reportInitDone :: LB () Source #
waitForInit :: MonadLB m => m () Source #
waitForQuit :: MonadLB m => m () Source #
data IRCRWState Source #
Global read/write state.
IRCRWState | |
|
Instances
MonadState IRCRWState LB Source # | |
Defined in Lambdabot.Monad get :: LB IRCRWState # put :: IRCRWState -> LB () # state :: (IRCRWState -> (a, IRCRWState)) -> LB a # |
initRwState :: IRCRWState Source #
Default rw state
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 # | |
MonadFail LB Source # | |
Defined in Lambdabot.Monad | |
Applicative LB Source # | |
MonadIO LB Source # | |
Defined in Lambdabot.Monad | |
MonadThrow LB Source # | |
Defined in Lambdabot.Monad | |
MonadCatch LB Source # | |
MonadMask 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, MonadFail m) => MonadLB m where Source #
registerModule :: String -> Module st -> st -> LB (ModuleInfo st) Source #
registerOutputFilter :: OutputFilter st -> ModuleT st LB () Source #
unregisterModule :: String -> LB () Source #
send :: IrcMessage -> LB () Source #
received :: IrcMessage -> LB () Source #
inModuleNamed :: String -> LB a -> (forall st. ModuleT st LB a) -> LB a Source #
Interpret an expression in the context of a module.
withCommand :: String -> LB a -> (forall st. Command (ModuleT st LB) -> ModuleT st LB a) -> LB a Source #
listModules :: LB [String] Source #