irc-client-1.1.0.0: An IRC client library.

Copyright(c) 2016 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityOverloadedStrings
Safe HaskellNone
LanguageHaskell2010

Network.IRC.Client

Contents

Description

A simple IRC client library. Typical usage will be of this form:

run :: ByteString -> Int -> Text -> IO ()
run host port nick = do
  let conn = plainConnection host port
  let cfg  = defaultInstanceConfig nick & handlers %~ (yourCustomEventHandlers:)
  runClient conn cfg ()

You shouldn't really need to tweak anything other than the event handlers, as everything has been designed to be as simple as possible.

Synopsis

Configuration

The configuration is logically split into two parts: the connection configuration (the ConnectionConfig type) and the instance configuration (the InstanceConfig type).

  • Connection configuration details how to connect to the IRC server, and cannot be modified after the client has started (although it can be read).
  • Instance configuration is everything else: the client's nick, and version, handlers for received messages, and so on. It can be modified after the client has started.

Connection configuration

The following values can be changed with the exported lenses:

  • username (default: "irc-client"). The username sent to the server in the "USER" command.
  • realname (default: "irc-client"). The real name sent to the server in the "USER" command.
  • password (default: Nothing). If set, the password sent to the server in the "PASS" command.
  • flood (default: 1). The minimum time between sending messages, to avoid flooding.
  • timeout (default: 300). The amount of time to wait for a message from the server before locally timing out.
  • onconnect (default: defaultOnConnect). The action to perform after sending the "USER" and "PASS" commands.
  • ondisconnect (default: defaultOnDisconnect). The action to perform after disconnecting from the server
  • logfunc (default: noopLogger). The function to log received and sent messages.

data ConnectionConfig s Source #

The static state of an IRC server connection.

plainConnection Source #

Arguments

:: ByteString

The hostname

-> Int

The port

-> ConnectionConfig s 

Connect to a server without TLS.

data TLSConfig Source #

How to connect to a server over TLS.

Constructors

WithDefaultConfig ByteString Int

Use Network.IRC.Conduit.defaultTLSConfig.

WithClientConfig TLSClientConfig

Use the given configuration. The hostname and port are stored as fields of the TLSClientConfig.

WithVerifier ByteString Int (CertificateStore -> ValidationCache -> ServiceID -> CertificateChain -> IO [FailedReason])

Use Network.IRC.Conduit.defaultTLSConfig, with the given certificate verifier. The certificate verifier is a function which returns a list of reasons to reject the certificate.

tlsConnection Source #

Arguments

:: TLSConfig

How to initiate the TLS connection

-> ConnectionConfig s 

Connect to a server with TLS.

Logging

The logging functions are told whether the message came from the server or the client, and are given the raw bytestring.

stdoutLogger :: Origin -> ByteString -> IO () Source #

Print messages to stdout, with the current time.

fileLogger :: FilePath -> Origin -> ByteString -> IO () Source #

Append messages to a file, with the current time.

noopLogger :: a -> b -> IO () Source #

Do no logging.

Instance configuration

The following values can be changed with the exported lenses:

data InstanceConfig s Source #

The updateable state of an IRC connection.

defaultInstanceConfig Source #

Arguments

:: Text

The nick

-> InstanceConfig s 

Construct a default IRC configuration from a nick

Writing IRC clients

With this library, IRC clients are mostly composed of event handlers. Event handlers are monadic actions operating in the IRC monad.

data IRC s a Source #

The IRC monad.

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 #

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 #

send :: Message Text -> IRC s () Source #

Send a message as UTF-8, using TLS if enabled. This blocks if messages are sent too rapidly.

sendBS :: Message ByteString -> IRC s () Source #

Send a message, using TLS if enabled. This blocks if messages are sent too rapidly.

disconnect :: IRC s () Source #

Disconnect from the server, properly tearing down the TLS session (if there is one).

reconnect :: IRC s () Source #

Disconnect from the server (this will wait for all messages to be sent, or a minute to pass), and then connect again.

This can be called after the client has already disconnected, in which case it will just connect again.

Like runClient and runClientWith, this will not return until the client terminates (ie, disconnects without reconnecting).

From event handlers

From the outside

The ConnectionConfig, InstanceConfig, and some other stuff are combined in the IRCState type. This can be used to interact with a client from the outside, by providing a way to run IRC s a actions.

data IRCState s Source #

The state of an IRC session.

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 #

getIRCState :: IRC s (IRCState s) Source #

Access the client state.

runIRCAction :: MonadIO m => IRC s a -> IRCState s -> m a Source #

Interact with a client from the outside, by using its IRCState.

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 # 

getConnectionState :: IRCState s -> STM ConnectionState Source #

Get the connection state from an IRC state.

Execution

runClient Source #

Arguments

:: MonadIO m 
=> ConnectionConfig s 
-> InstanceConfig s 
-> s

The initial value for the user state.

-> m () 

Connect to the IRC server and run the client: receiving messages and handing them off to handlers as appropriate.

If an IRCState is constructed with newIRCState and a client started with runClientWith, then runIRCAction can be used to interact with that client.

newIRCState Source #

Arguments

:: MonadIO m 
=> ConnectionConfig s 
-> InstanceConfig s 
-> s

The initial value for the user state.

-> m (IRCState s) 

Construct a new IRC state

runClientWith :: MonadIO m => IRCState s -> m () Source #

Like runClient, but use the provided initial IRCState.

Multiple clients should not be run with the same IRCState. The utility of this is to be able to run IRC s a actions in order to interact with the client from the outside.

If the client times out from the server, the Timeout exception will be thrown, killing it.

Concurrency

A client can manage a collection of threads, which get thrown the Disconnect exception whenever the client disconnects for any reason (including a call to reconnect). These can be created from event handlers to manage long-running tasks.

fork :: IRC s () -> IRC s ThreadId Source #

Fork a thread which will be thrown a Disconnect exception when the client disconnects.

data Disconnect Source #

Exception thrown to all managed threads when the client disconnects.

Constructors

Disconnect 

Lenses

Utilities

rawMessage #

Arguments

:: ByteString

The command

-> [ByteString]

The arguments

-> IrcMessage 

Construct a raw message.

toByteString :: IrcMessage -> ByteString #

Encode an IRC message into a single bytestring suitable for sending to the server.