| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Lambdabot.Monad
- data IRCRState
- initRoState :: [DSum Config] -> IO IRCRState
- reportInitDone :: MonadIO m => IRCRState -> m ()
- waitForInit :: MonadLB m => m ()
- waitForQuit :: MonadLB m => m ()
- type Callback = IrcMessage -> LB ()
- data ModuleRef = forall st . ModuleRef (Module st) (MVar st) String
- data CommandRef = forall st . CommandRef (Module st) (MVar st) String (Command (ModuleT st LB))
- data IRCRWState = IRCRWState {
- ircServerMap :: Map String (String, IrcMessage -> LB ())
- ircPrivilegedUsers :: Set Nick
- ircIgnoredUsers :: Set Nick
- ircChannels :: Map ChanName String
- ircModules :: Map String ModuleRef
- ircCallbacks :: Map String [(String, Callback)]
- ircOutputFilters :: [(String, OutputFilter LB)]
- ircCommands :: Map String CommandRef
- ircStayConnected :: !Bool
- initRwState :: IRCRWState
- newtype LB a = LB {}
- class (MonadIO m, MonadBaseControl IO m, MonadConfig m, MonadLogging m, Applicative m) => MonadLB m where
- evalLB :: LB a -> IRCRState -> IRCRWState -> IO a
- addServer :: String -> (IrcMessage -> LB ()) -> ModuleT mod LB ()
- remServer :: String -> LB ()
- send :: IrcMessage -> LB ()
- received :: IrcMessage -> LB ()
- getConfig :: MonadConfig m => Config a -> m a
- withModule :: String -> LB a -> (forall st. Module st -> ModuleT st LB a) -> LB a
- withCommand :: String -> LB a -> (forall st. Module st -> Command (ModuleT st LB) -> ModuleT st LB a) -> LB a
- withAllModules :: (forall st. Module st -> ModuleT st LB a) -> LB ()
Documentation
reportInitDone :: MonadIO m => IRCRState -> m () Source
waitForInit :: MonadLB m => m () Source
waitForQuit :: MonadLB m => m () Source
type Callback = IrcMessage -> LB () Source
data CommandRef Source
data IRCRWState Source
Global read/write state.
Constructors
| IRCRWState | |
Fields
| |
Instances
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 | |
| Functor LB | |
| Applicative LB | |
| MonadIO LB | |
| MonadException LB | |
| MonadRandom LB | |
| MonadConfig LB | |
| MonadLogging LB | |
| MonadLB LB | |
| MonadBase IO LB | |
| MonadBaseControl IO LB | |
| MonadState IRCRWState LB | |
| type StM LB a = StM (ReaderT (IRCRState, IORef IRCRWState) IO) a |
class (MonadIO m, MonadBaseControl IO m, MonadConfig m, MonadLogging m, Applicative m) => MonadLB m where Source
send :: IrcMessage -> LB () Source
received :: IrcMessage -> LB () Source
getConfig :: MonadConfig m => Config a -> m a Source
withModule :: String -> LB a -> (forall st. Module st -> ModuleT st LB a) -> LB a Source
Interpret an expression in the context of a module.
Arguments are which map to use (ircModules and ircCommands are
the only sensible arguments here), the name of the module/command,
action for the case that the lookup fails, action if the lookup
succeeds.