irc-conduit-0.3.0.3: Streaming IRC message library using conduits.

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

Network.IRC.Conduit

Contents

Description

Conduits for serialising and deserialising IRC messages.

The Event, Message, and Source types are parameterised on the underlying representation, and are functors. Decoding and encoding only work in terms of ByteStrings, but the generality is provided so that programs using this library can operate in terms of Text, or some other more useful representation, with great ease.

Synopsis

Type synonyms

type ChannelName a = a Source #

type NickName a = a Source #

type ServerName a = a Source #

type Reason a = Maybe a Source #

type ModeFlag a = a Source #

type ModeArg a = a Source #

type NumericArg a = a Source #

type Target a = a Source #

The target of a message. Will be a nick or channel name.

Messages

data Event a Source #

A decoded IRC message + source.

Constructors

Event 

Fields

Instances
Functor Event Source # 
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) Source # 
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) Source # 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

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

show :: Event a -> String #

showList :: [Event a] -> ShowS #

data Source a Source #

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 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) Source # 
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) Source # 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

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

show :: Source a -> String #

showList :: [Source a] -> ShowS #

data Message a Source #

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 Source # 
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) Source # 
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) Source # 
Instance details

Defined in Network.IRC.Conduit.Internal

Methods

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

show :: Message a -> String #

showList :: [Message a] -> ShowS #

Conduits

ircDecoder :: Monad m => ConduitM ByteString (Either ByteString IrcEvent) m () Source #

A conduit which takes as input bytestrings representing encoded IRC messages, and decodes them to events. If decoding fails, the original bytestring is just passed through.

ircLossyDecoder :: Monad m => ConduitM ByteString IrcEvent m () Source #

Like ircDecoder, but discards messages which could not be decoded.

ircEncoder :: Monad m => ConduitM IrcMessage ByteString m () Source #

A conduit which takes as input irc messages, and produces as output the encoded bytestring representation.

floodProtector Source #

Arguments

:: MonadIO m 
=> NominalDiffTime

The minimum time between sending adjacent messages.

-> IO (ConduitM a a m ()) 

A conduit which rate limits output sent downstream. Awaiting on this conduit will block, even if there is output ready, until the time limit has passed.

Networking

ircClient Source #

Arguments

:: Int

The port number

-> ByteString

The hostname

-> IO ()

Any initialisation work (started concurrently with the producer and consumer)

-> ConduitM (Either ByteString IrcEvent) Void IO ()

The consumer of irc events

-> ConduitM () IrcMessage IO ()

The producer of irc messages

-> IO () 

Connect to a network server, without TLS, and concurrently run the producer and consumer.

ircWithConn Source #

Arguments

:: ((AppData -> IO ()) -> IO ())

The initialised connection.

-> IO () 
-> ConduitM (Either ByteString IrcEvent) Void IO () 
-> ConduitM () IrcMessage IO () 
-> IO () 

Run the IRC conduits using a provided connection.

Starts the connection and concurrently run the initialiser, event consumer, and message sources. Terminates as soon as one throws an exception.

TLS

ircTLSClient :: Int -> ByteString -> IO () -> ConduitM (Either ByteString IrcEvent) Void IO () -> ConduitM () IrcMessage IO () -> IO () Source #

Like ircClient, but with TLS. The TLS configuration used is defaultTLSConfig.

ircTLSClient' :: TLSClientConfig -> IO () -> ConduitM (Either ByteString IrcEvent) Void IO () -> ConduitM () IrcMessage IO () -> IO () Source #

Like ircTLSClient, but takes the configuration to use, which includes the host and port.

defaultTLSConfig Source #

Arguments

:: Int

The port number

-> ByteString

The hostname

-> TLSClientConfig 

The default TLS settings for ircTLSClient.

Utilities

rawMessage Source #

Arguments

:: ByteString

The command

-> [ByteString]

The arguments

-> IrcMessage 

Construct a raw message.

toByteString :: IrcMessage -> ByteString Source #

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

Lenses