irc-client-1.1.0.5: An IRC client library.

Copyright(c) 2017 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityCPP, OverloadedStrings, RankNTypes
Safe HaskellNone
LanguageHaskell2010

Network.IRC.Client.Events

Contents

Description

Events and event handlers. When a message is received from the server, all matching handlers are executed sequentially in the order that they appear in the handlers list.

Synopsis

Handlers

data EventHandler s where Source #

A function which handles an event.

Constructors

EventHandler :: (Event Text -> Maybe b) -> (Source Text -> b -> IRC s ()) -> EventHandler s 

matchCTCP :: Text -> Event Text -> Maybe [Text] Source #

Match the verb of a CTCP, ignoring case, and returning the arguments.

matchCTCP "ping"   ":foo PRIVMSG #bar :\001PING\001"          ==> Just []
matchCTCP "PING"   ":foo PRIVMSG #bar :\001PING\001"          ==> Just []
matchCTCP "ACTION" ":foo PRIVMSG #bar :\001ACTION dances\001" ==> Just ["dances"]

matchNumeric :: Int -> Event a -> Maybe [a] Source #

Match a numeric server message. Numeric messages are sent in response to most things, such as connecting to the server, or joining a channel.

Numerics in the range 001 to 099 are informative messages, numerics in the range 200 to 399 are responses to commands. Some common numerics are:

  • 001 (RPL_WELCOME), sent after successfully connecting.
  • 331 (RPL_NOTOPIC), sent after joining a channel if it has no topic.
  • 332 (RPL_TOPIC), sent after joining a channel if it has a topic.
  • 432 (ERR_ERRONEUSNICKNAME), sent after trying to change to an invalid nick.
  • 433 (ERR_NICKNAMEINUSE), sent after trying to change to a nick already in use.
  • 436 (ERR_NICKCOLLISION), sent after trying to change to a nick in use on another server.

See Section 5 of <https://tools.ietf.org/html/rfc2812#section-5 RFC 2812> for a complete list.

matchNumeric 001 "001 :Welcome to irc.example.com" ==> True
matchNumeric 332 "332 :#haskell: We like Haskell"  ==> True

matchType :: Prism' (Message a) b -> Event a -> Maybe b Source #

Match events of the given type. Refer to Network.IRC.Conduit.Lens for the list of Prism's.

matchType _Privmsg ":foo PRIVMSG #bar :hello world" ==> Just ("#bar", Right "hello world")
matchType _Quit    ":foo QUIT :goodbye world"       ==> Just (Just "goodbye world")

matchWhen :: (Event a -> Bool) -> Event a -> Maybe (Message a) Source #

Match a predicate against an event.

matchWhen (const True) ":foo PRIVMSG #bar :hello world" ==> Just ":foo PRIVMSG :hello world"

Default handlers

defaultEventHandlers :: [EventHandler s] Source #

The default event handlers, the following are included:

  • respond to server PING messages with a PONG;
  • respond to CTCP PING requests;
  • respond to CTCP VERSION requests with the version string;
  • respond to CTCP TIME requests with the system time;
  • update the nick upon receiving the welcome message, in case the server modifies it;
  • mangle the nick if the server reports a collision;
  • update the channel list on JOIN and KICK.

defaultOnConnect :: IRC s () Source #

The default connect handler: set the nick.

defaultOnDisconnect :: Maybe SomeException -> IRC s () Source #

The default disconnect handler

  • If the client disconnected due to a Timeout exception, reconnect.
  • If the client disconnected due to another exception, rethrow it.
  • If the client disconnected without an exception, halt.

Individual handlers

pingHandler :: EventHandler s Source #

Respond to server PING messages with a PONG.

ctcpPingHandler :: EventHandler s Source #

Respond to CTCP PING requests.

ctcpVersionHandler :: EventHandler s Source #

Respond to CTCP VERSION requests with the version string.

ctcpTimeHandler :: EventHandler s Source #

Respond to CTCP TIME requests with the system time.

welcomeNick :: EventHandler s Source #

Update the nick upon welcome (numeric reply 001), as it may not be what we requested (eg, in the case of a nick too long).

joinOnWelcome :: EventHandler s Source #

Join default channels upon welcome (numeric reply 001). If sent earlier, the server might reject the JOIN attempts.

joinHandler :: EventHandler s Source #

Upon joining a channel (numeric reply 331 or 332), add it to the list (if not already present).

nickMangler :: EventHandler s Source #

Mangle the nick if there's a collision (numeric replies 432, 433, and 436) when we set it

Re-exported

data Event a #

A decoded IRC message + source.

Constructors

Event 

Fields

Instances
Functor Event 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

Eq (NickName a) => Eq (Event a) 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

(==) :: Event a -> Event a -> Bool #

(/=) :: Event a -> Event a -> Bool #

Show (NickName a) => Show (Event a) 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

data Message a #

A decoded IRC message.

Constructors

Privmsg (Target a) (Either CTCPByteString a)

A message, either from a user or to a channel the client is in. CTCPs are distinguished by starting and ending with a \001 (SOH).

Notice (Target a) (Either CTCPByteString a)

Like a privmsg, but should not provoke an automatic response.

Nick (NickName a)

Someone has updated their nick.

Join (ChannelName a)

Someone has joined a channel.

Part (ChannelName a) (Reason a)

Someone has left a channel.

Quit (Reason a)

Someone has left the network.

Mode (Target a) IsModeSet [ModeFlag a] [ModeArg a]

Someone has set some channel modes or user modes.

Topic (ChannelName a) a

Someone has set the topic of a channel.

Invite (ChannelName a) (NickName a)

The client has been invited to a channel.

Kick (ChannelName a) (NickName a) (Reason a)

Someone has been kicked from a channel.

Ping (ServerName a) (Maybe (ServerName a))

The client has received a server ping, and should send a pong asap.

Pong (ServerName a)

A pong sent to the named server.

Numeric Int [NumericArg a]

One of the many server numeric responses.

RawMsg a

Never produced by decoding, but can be used to send arbitrary bytestrings to the IRC server. Naturally, this should only be used when you are confident that the produced bytestring will be a valid IRC message.

Instances
Functor Message 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

fmap :: (a -> b) -> Message a -> Message b #

(<$) :: a -> Message b -> Message a #

Eq (Target a) => Eq (Message a) 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

(==) :: Message a -> Message a -> Bool #

(/=) :: Message a -> Message a -> Bool #

Show (Target a) => Show (Message a) 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

showsPrec :: Int -> Message a -> ShowS #

show :: Message a -> String #

showList :: [Message a] -> ShowS #

data Source a #

The source of an IRC message.

Constructors

User (NickName a)

The message comes directly from a user.

Channel (ChannelName a) (NickName a)

The message comes from a user in a channel.

Server (ServerName a)

The message comes directly from the server.

Instances
Functor Source 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

fmap :: (a -> b) -> Source a -> Source b #

(<$) :: a -> Source b -> Source a #

Eq (NickName a) => Eq (Source a) 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

(==) :: Source a -> Source a -> Bool #

(/=) :: Source a -> Source a -> Bool #

Show (NickName a) => Show (Source a) 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

showsPrec :: Int -> Source a -> ShowS #

show :: Source a -> String #

showList :: [Source a] -> ShowS #