Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 ByteString
s, 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.
- type ChannelName a = a
- type NickName a = a
- type ServerName a = a
- type Reason a = Maybe a
- type IsModeSet = Bool
- type ModeFlag a = a
- type ModeArg a = a
- type NumericArg a = a
- type Target a = a
- type IrcEvent = Event ByteString
- type IrcSource = Source ByteString
- type IrcMessage = Message ByteString
- data Event a = Event {}
- data Source a
- = User (NickName a)
- | Channel (ChannelName a) (NickName a)
- | Server (ServerName a)
- data Message a
- = Privmsg (Target a) (Either CTCPByteString a)
- | Notice (Target a) (Either CTCPByteString a)
- | Nick (NickName a)
- | Join (ChannelName a)
- | Part (ChannelName a) (Reason a)
- | Quit (Reason a)
- | Mode (Target a) IsModeSet [ModeFlag a] [ModeArg a]
- | Topic (ChannelName a) a
- | Invite (ChannelName a) (NickName a)
- | Kick (ChannelName a) (NickName a) (Reason a)
- | Ping (ServerName a) (Maybe (ServerName a))
- | Pong (ServerName a)
- | Numeric Int [NumericArg a]
- | RawMsg a
- ircDecoder :: Monad m => Conduit ByteString m (Either ByteString IrcEvent)
- ircLossyDecoder :: Monad m => Conduit ByteString m IrcEvent
- ircEncoder :: Monad m => Conduit IrcMessage m ByteString
- floodProtector :: MonadIO m => NominalDiffTime -> IO (Conduit a m a)
- ircClient :: Int -> ByteString -> IO () -> Consumer (Either ByteString IrcEvent) IO () -> Producer IO IrcMessage -> IO ()
- ircTLSClient :: Int -> ByteString -> IO () -> Consumer (Either ByteString IrcEvent) IO () -> Producer IO IrcMessage -> IO ()
- ircWithConn :: ((AppData -> IO ()) -> IO ()) -> IO () -> Consumer (Either ByteString IrcEvent) IO () -> Producer IO IrcMessage -> IO ()
- rawMessage :: ByteString -> [ByteString] -> IrcMessage
- toByteString :: IrcMessage -> ByteString
Type synonyms
type ChannelName a = a Source
type ServerName a = a Source
type NumericArg a = a Source
type IrcEvent = Event ByteString Source
type IrcSource = Source ByteString Source
type IrcMessage = Message ByteString Source
Messages
A decoded IRC message + source.
The source of an IRC message.
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. |
A decoded IRC message.
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. |
Conduits
ircDecoder :: Monad m => Conduit ByteString m (Either ByteString IrcEvent) 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 => Conduit ByteString m IrcEvent Source
Like ircDecoder
, but discards messages which could not be
decoded.
ircEncoder :: Monad m => Conduit IrcMessage m ByteString Source
A conduit which takes as input irc messages, and produces as output the encoded bytestring representation.
:: MonadIO m | |
=> NominalDiffTime | The minimum time between sending adjacent messages. |
-> IO (Conduit a m a) |
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
:: Int | The port number |
-> ByteString | The hostname |
-> IO () | Any initialisation work (started concurrently with the producer and consumer) |
-> Consumer (Either ByteString IrcEvent) IO () | The consumer of irc events |
-> Producer IO IrcMessage | The producer of irc messages |
-> IO () |
Connect to a network server, without TLS, and concurrently run the producer and consumer.
ircTLSClient :: Int -> ByteString -> IO () -> Consumer (Either ByteString IrcEvent) IO () -> Producer IO IrcMessage -> IO () Source
Like ircClient
, but with TLS.
:: ((AppData -> IO ()) -> IO ()) | The initialised connection. |
-> IO () | |
-> Consumer (Either ByteString IrcEvent) IO () | |
-> Producer IO IrcMessage | |
-> IO () |
Run the IRC conduits using a provided connection.
Utilities
:: 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.