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

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

Network.IRC.Conduit.Internal

Contents

Description

Internal IRC conduit types and utilities. This module is NOT considered to form part of the public interface of this library.

Synopsis

Internal Lens synonyms

type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t Source #

type Lens' s a = Lens s s a a Source #

type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) Source #

type Prism' s a = Prism s s a a Source #

Conduits

chunked :: Monad m => ConduitM ByteString ByteString m () Source #

Split up incoming bytestrings into new lines.

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 # 

Methods

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

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

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

Methods

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

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

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

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 # 

Methods

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

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

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

Methods

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

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

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

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 # 

Methods

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

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

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

Methods

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

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

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

Methods

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

show :: Message a -> String #

showList :: [Message a] -> ShowS #

Decoding messages

attemptDecode :: ByteString -> Maybe (IrcSource, IrcMessage) Source #

Attempt to decode a ByteString into a message, returning a Nothing if either the source or the message can't be determined.

Encoding messages

toByteString :: IrcMessage -> ByteString Source #

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

rawMessage Source #

Arguments

:: ByteString

The command

-> [ByteString]

The arguments

-> IrcMessage 

Construct a raw message.