ircbot-0.6.6.1: A library for writing IRC bots
Safe HaskellNone
LanguageHaskell2010

Network.IRC.Bot.Commands

Contents

Synopsis

Documentation

Commands

cmd :: (Functor m, MonadPlus m, BotMonad m) => Command -> m () Source #

data Ping Source #

Constructors

Ping HostName 

Instances

Instances details
Eq Ping Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

(==) :: Ping -> Ping -> Bool #

(/=) :: Ping -> Ping -> Bool #

Data Ping Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

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 #

toConstr :: Ping -> Constr #

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 # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

compare :: Ping -> Ping -> Ordering #

(<) :: Ping -> Ping -> Bool #

(<=) :: Ping -> Ping -> Bool #

(>) :: Ping -> Ping -> Bool #

(>=) :: Ping -> Ping -> Bool #

max :: Ping -> Ping -> Ping #

min :: Ping -> Ping -> Ping #

Read Ping Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Show Ping Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

showsPrec :: Int -> Ping -> ShowS #

show :: Ping -> String #

showList :: [Ping] -> ShowS #

data PrivMsg Source #

Constructors

PrivMsg 

Instances

Instances details
Eq PrivMsg Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

(==) :: PrivMsg -> PrivMsg -> Bool #

(/=) :: PrivMsg -> PrivMsg -> Bool #

Read PrivMsg Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Show PrivMsg Source # 
Instance details

Defined in Network.IRC.Bot.Commands

ToMessage PrivMsg Source # 
Instance details

Defined in Network.IRC.Bot.Commands

class ToMessage a where Source #

Methods

toMessage :: a -> Message Source #

Instances

Instances details
ToMessage Notice Source # 
Instance details

Defined in Network.IRC.Bot.Commands

ToMessage Pong Source # 
Instance details

Defined in Network.IRC.Bot.Commands

ToMessage PrivMsg Source # 
Instance details

Defined in Network.IRC.Bot.Commands

sendCommand :: (ToMessage c, BotMonad m, Functor m) => c -> m () Source #

data Pong Source #

Constructors

Pong HostName 

Instances

Instances details
Eq Pong Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

(==) :: Pong -> Pong -> Bool #

(/=) :: Pong -> Pong -> Bool #

Data Pong Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

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 #

toConstr :: Pong -> Constr #

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 # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

compare :: Pong -> Pong -> Ordering #

(<) :: Pong -> Pong -> Bool #

(<=) :: Pong -> Pong -> Bool #

(>) :: Pong -> Pong -> Bool #

(>=) :: Pong -> Pong -> Bool #

max :: Pong -> Pong -> Pong #

min :: Pong -> Pong -> Pong #

Read Pong Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Show Pong Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

showsPrec :: Int -> Pong -> ShowS #

show :: Pong -> String #

showList :: [Pong] -> ShowS #

ToMessage Pong Source # 
Instance details

Defined in Network.IRC.Bot.Commands

data Notice Source #

Instances

Instances details
Eq Notice Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Methods

(==) :: Notice -> Notice -> Bool #

(/=) :: Notice -> Notice -> Bool #

Read Notice Source # 
Instance details

Defined in Network.IRC.Bot.Commands

Show Notice Source # 
Instance details

Defined in Network.IRC.Bot.Commands

ToMessage Notice Source # 
Instance details

Defined in Network.IRC.Bot.Commands

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