irc-client-0.4.2.1: 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

data ConnectionState Source #

The state of the connection.

Instances

Bounded ConnectionState Source # 
Enum ConnectionState Source # 
Eq ConnectionState Source # 
Ord ConnectionState Source # 
Read ConnectionState Source # 
Show ConnectionState Source # 

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

getConnState :: MonadIO m => IRCState s -> m ConnectionState Source #

Extract the connection 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

data InstanceConfig s Source #

The updateable state of an IRC connection.

Constructors

InstanceConfig 

Fields

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

eventType :: Event a -> EventType Source #

Get the type of an event.

Re-exported

data Event a :: * -> * #

A decoded IRC message + source.

Constructors

Event 

Fields

Instances

Functor Event 

Methods

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

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

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

Methods

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

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

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

Methods

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

show :: Event a -> String #

showList :: [Event 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 

Methods

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

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

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

Methods

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

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

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

Methods

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

show :: Source a -> String #

showList :: [Source 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 

Methods

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

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

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

Methods

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

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

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

Methods

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

show :: Message a -> String #

showList :: [Message a] -> ShowS #