irc-client-0.2.6.0: An IRC client library.

Safe HaskellNone
LanguageHaskell2010

Network.IRC.Client.Types

Contents

Description

Types for IRC clients. See also Network.IRC.Conduit and Network.IRC.CTCP.

Synopsis

Type synonyms

State

type IRC a = StatefulIRC () a Source

The IRC monad.

type StatefulIRC s a = ReaderT (IRCState s) IO a Source

The IRC monad, with state.

data IRCState s Source

Constructors

IRCState 

Fields

_connectionConfig :: ConnectionConfig s

Read-only connection configuration

_userState :: TVar s

Mutable user state

_instanceConfig :: TVar (InstanceConfig s)

Mutable instance configuration in STM

newIRCState :: MonadIO m => ConnectionConfig s -> InstanceConfig s -> s -> m (IRCState s) Source

Construct a new IRC state

ircState :: StatefulIRC s (IRCState s) Source

Access the client state.

getConnectionConfig :: IRCState s -> ConnectionConfig s Source

Extract the connection configuration from an IRC state

getInstanceConfig :: IRCState s -> TVar (InstanceConfig s) Source

Extract the instance configuration from an IRC state

getUserState :: IRCState s -> TVar s Source

Extract the user state from an IRC state

getInstanceConfig' :: MonadIO m => IRCState s -> m (InstanceConfig s) Source

Extract the current snapshot of the instance configuration from an IRC state

connectionConfig :: StatefulIRC s (ConnectionConfig s) Source

Access the connection config

instanceConfigTVar :: StatefulIRC s (TVar (InstanceConfig s)) Source

Access the instance config TVar

instanceConfig :: StatefulIRC s (InstanceConfig s) Source

Access the instance config as it is right now.

putInstanceConfig :: InstanceConfig s -> StatefulIRC s () Source

Overwrite the instance config, even if it has changed since we looked at it.

stateTVar :: StatefulIRC s (TVar s) Source

Access the user state.

state :: StatefulIRC s s Source

Access the user state as it is right now.

putState :: s -> StatefulIRC s () Source

Set the user state.

data Origin Source

The origin of a message.

Constructors

FromServer 
FromClient 

data ConnectionConfig s Source

The static state of an IRC server connection.

Constructors

ConnectionConfig 

Fields

_func :: Int -> ByteString -> IO () -> Consumer (Either ByteString IrcEvent) IO () -> Producer IO IrcMessage -> IO ()

Function to connect and start the conduits.

_sendqueue :: TBMChan IrcMessage

Message send queue.

_server :: ByteString

The server host.

_port :: Int

The server port.

_flood :: NominalDiffTime

The minimum time between two adjacent messages.

_disconnect :: StatefulIRC s ()

Action to run if the remote server closes the connection.

_logfunc :: Origin -> ByteString -> IO ()

Function to log messages sent to and received from the server.

data InstanceConfig s Source

The updateable state of an IRC connection.

Constructors

InstanceConfig 

Fields

_nick :: Text

Client nick

_username :: Text

Client username

_realname :: Text

Client realname

_channels :: [Text]

Current channels

_ctcpVer :: Text

Response to CTCP VERSION

_eventHandlers :: [EventHandler s]

The registered event handlers

_ignore :: [(Text, Maybe Text)]

List of nicks (optionally restricted to channels) to ignore messages from. No channel = global.

Events

data EventType Source

Types of events which can be caught.

Constructors

EEverything

Match all events

ENothing

Match no events

EPrivmsg 
ENotice 
ECTCP 
ENick 
EJoin 
EPart 
EQuit 
EMode 
ETopic 
EInvite 
EKick 
EPing 
ENumeric 

data EventHandler s Source

A function which handles an event.

Constructors

EventHandler 

Fields

_description :: Text

A description of the event handler.

_matchType :: EventType

Which type to be triggered by

_eventFunc :: UnicodeEvent -> StatefulIRC s ()

The function to call.

eventType :: Event a -> EventType Source

Get the type of an event.

Re-exported

data Event a :: * -> *

A decoded IRC message + source.

Constructors

Event 

Fields

_raw :: ByteString

The message as a bytestring.

_source :: Source a

The source of the message (user, channel, or server).

_message :: Message a

The decoded message. This will never be a RawMsg.

Instances

Functor Event 
Eq (NickName a) => Eq (Event a) 
Show (NickName a) => Show (Event a) 

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

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 
Eq (Target a) => Eq (Message a) 
Show (Target a) => Show (Message a)