irc-client-1.1.0.2: An IRC client library.

Copyright(c) 2017 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityFlexibleInstances, GADTs, GeneralizedNewtypeDeriving, MultiParamTypeClasses
Safe HaskellNone
LanguageHaskell2010

Network.IRC.Client.Internal.Types

Contents

Description

Internal types. Most of these are re-exported elsewhere as lenses.

This module is NOT considered to form part of the public interface of this library.

Synopsis

The IRC monad

newtype IRC s a Source #

The IRC monad.

Constructors

IRC 

Fields

Instances

MonadState s (IRC s) Source # 

Methods

get :: IRC s s #

put :: s -> IRC s () #

state :: (s -> (a, s)) -> IRC s a #

Monad (IRC s) Source # 

Methods

(>>=) :: IRC s a -> (a -> IRC s b) -> IRC s b #

(>>) :: IRC s a -> IRC s b -> IRC s b #

return :: a -> IRC s a #

fail :: String -> IRC s a #

Functor (IRC s) Source # 

Methods

fmap :: (a -> b) -> IRC s a -> IRC s b #

(<$) :: a -> IRC s b -> IRC s a #

Applicative (IRC s) Source # 

Methods

pure :: a -> IRC s a #

(<*>) :: IRC s (a -> b) -> IRC s a -> IRC s b #

liftA2 :: (a -> b -> c) -> IRC s a -> IRC s b -> IRC s c #

(*>) :: IRC s a -> IRC s b -> IRC s b #

(<*) :: IRC s a -> IRC s b -> IRC s a #

Alternative (IRC s) Source # 

Methods

empty :: IRC s a #

(<|>) :: IRC s a -> IRC s a -> IRC s a #

some :: IRC s a -> IRC s [a] #

many :: IRC s a -> IRC s [a] #

MonadPlus (IRC s) Source # 

Methods

mzero :: IRC s a #

mplus :: IRC s a -> IRC s a -> IRC s a #

MonadIO (IRC s) Source # 

Methods

liftIO :: IO a -> IRC s a #

MonadThrow (IRC s) Source # 

Methods

throwM :: Exception e => e -> IRC s a #

MonadCatch (IRC s) Source # 

Methods

catch :: Exception e => IRC s a -> (e -> IRC s a) -> IRC s a #

MonadMask (IRC s) Source # 

Methods

mask :: ((forall a. IRC s a -> IRC s a) -> IRC s b) -> IRC s b #

uninterruptibleMask :: ((forall a. IRC s a -> IRC s a) -> IRC s b) -> IRC s b #

generalBracket :: IRC s a -> (a -> IRC s ignored1) -> (a -> SomeException -> IRC s ignored2) -> (a -> IRC s b) -> IRC s b #

MonadReader (IRCState s) (IRC s) Source # 

Methods

ask :: IRC s (IRCState s) #

local :: (IRCState s -> IRCState s) -> IRC s a -> IRC s a #

reader :: (IRCState s -> a) -> IRC s a #

State

data IRCState s Source #

The state of an IRC session.

Constructors

IRCState 

Fields

Instances

MonadReader (IRCState s) (IRC s) Source # 

Methods

ask :: IRC s (IRCState s) #

local :: (IRCState s -> IRCState s) -> IRC s a -> IRC s a #

reader :: (IRCState s -> a) -> IRC s a #

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

  • _nick :: Text

    Client nick

  • _channels :: [Text]

    Current channels: this list both determines the channels to join on connect, and is modified by the default event handlers when channels are joined or parted.

  • _version :: Text

    The version is sent in response to the CTCP "VERSION" request by the default event handlers.

  • _handlers :: [EventHandler s]

    The registered event handlers. The order in this list is the order in which they are executed.

  • _ignore :: [(Text, Maybe Text)]

    List of nicks (optionally restricted to channels) to ignore messages from. Nothing ignores globally.

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 # 

Events

data EventHandler s where Source #

A function which handles an event.

Constructors

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

Exceptions

data Disconnect Source #

Exception thrown to all managed threads when the client disconnects.

Constructors

Disconnect