Copyright | (c) 2016 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | BangPatterns, DeriveFunctor, OverloadedStrings, RankNTypes, TupleSections |
Safe Haskell | None |
Language | Haskell2010 |
Internal IRC conduit types and utilities. This module is NOT considered to form part of the public interface of this library.
Synopsis
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type Prism' s a = Prism s s a a
- chunked :: Monad m => ConduitM ByteString ByteString m ()
- 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
- fromByteString :: ByteString -> Either ByteString IrcEvent
- attemptDecode :: ByteString -> Maybe (IrcSource, IrcMessage)
- toByteString :: IrcMessage -> ByteString
- mkMessage :: ByteString -> [ByteString] -> ByteString
- rawMessage :: ByteString -> [ByteString] -> IrcMessage
Internal Lens synonyms
type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) 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 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. |
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.
mkMessage :: ByteString -> [ByteString] -> ByteString Source #
:: ByteString | The command |
-> [ByteString] | The arguments |
-> IrcMessage |
Construct a raw message.