Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type HostName = ByteString
- cmd :: (Functor m, MonadPlus m, BotMonad m) => Command -> m ()
- data Ping = Ping HostName
- ping :: (Functor m, MonadPlus m, BotMonad m) => m Ping
- data PrivMsg = PrivMsg {
- prefix :: Maybe Prefix
- receivers :: [ByteString]
- msg :: ByteString
- privMsg :: (Functor m, MonadPlus m, BotMonad m) => m PrivMsg
- toPrivMsg :: Message -> Maybe PrivMsg
- class ToMessage a where
- sendCommand :: (ToMessage c, BotMonad m, Functor m) => c -> m ()
- data Pong = Pong HostName
- data Notice = Notice {}
- askSenderNickName :: BotMonad m => m (Maybe ByteString)
- replyTo :: BotMonad m => m (Maybe ByteString)
- askReceiver :: (Alternative m, BotMonad m) => m (Maybe ByteString)
Documentation
type HostName = ByteString Source #
Commands
Instances
Eq Ping Source # | |
Data Ping Source # | |
Defined in Network.IRC.Bot.Commands gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ping -> c Ping # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ping # dataTypeOf :: Ping -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ping) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ping) # gmapT :: (forall b. Data b => b -> b) -> Ping -> Ping # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ping -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ping -> r # gmapQ :: (forall d. Data d => d -> u) -> Ping -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ping -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ping -> m Ping # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ping -> m Ping # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ping -> m Ping # | |
Ord Ping Source # | |
Read Ping Source # | |
Show Ping Source # | |
PrivMsg | |
|
Instances
Eq Pong Source # | |
Data Pong Source # | |
Defined in Network.IRC.Bot.Commands gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pong -> c Pong # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Pong # dataTypeOf :: Pong -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Pong) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Pong) # gmapT :: (forall b. Data b => b -> b) -> Pong -> Pong # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pong -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pong -> r # gmapQ :: (forall d. Data d => d -> u) -> Pong -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pong -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pong -> m Pong # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pong -> m Pong # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pong -> m Pong # | |
Ord Pong Source # | |
Read Pong Source # | |
Show Pong Source # | |
ToMessage Pong Source # | |
askSenderNickName :: BotMonad m => m (Maybe ByteString) Source #
get the nickname of the user who sent the message
replyTo :: BotMonad m => m (Maybe ByteString) Source #
figure out who to reply to for a given Message
If message was sent to a #channel reply to the channel. Otherwise reply to the sender.
askReceiver :: (Alternative m, BotMonad m) => m (Maybe ByteString) Source #
returns the receiver of a message
if multiple receivers, it returns only the first