| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.IRC.Client
Description
A simple IRC client library. Typical usage will be of this form:
run :: ByteString -> Int -> Text -> IO ()
run host port nick = do
conn <- connect host port 1
let cfg = defaultIRCConf nick
let cfg' = cfg { _handlers = yourCustomEventHandlers : _handlers cfg }
start 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.
- connect :: MonadIO m => ByteString -> Int -> NominalDiffTime -> m ConnectionConfig
- connectWithTLS :: MonadIO m => ByteString -> Int -> NominalDiffTime -> m ConnectionConfig
- start :: MonadIO m => ConnectionConfig -> InstanceConfig -> m ()
- start' :: MonadIO m => IRCState -> m ()
- data Origin
- connect' :: MonadIO m => (Origin -> ByteString -> IO ()) -> ByteString -> Int -> NominalDiffTime -> m ConnectionConfig
- connectWithTLS' :: MonadIO m => (Origin -> ByteString -> IO ()) -> ByteString -> Int -> NominalDiffTime -> m ConnectionConfig
- stdoutLogger :: Origin -> ByteString -> IO ()
- fileLogger :: FilePath -> Origin -> ByteString -> IO ()
- noopLogger :: a -> b -> IO ()
- send :: UnicodeMessage -> IRC ()
- sendBS :: IrcMessage -> IRC ()
- disconnect :: IRC ()
- defaultIRCConf :: Text -> InstanceConfig
- defaultDisconnectHandler :: IRC ()
- defaultEventHandlers :: [EventHandler]
- module Network.IRC.Client.Types
- module Network.IRC.Client.Utils
- rawMessage :: ByteString -> [ByteString] -> IrcMessage
- toByteString :: IrcMessage -> ByteString
Initialisation
Arguments
| :: MonadIO m | |
| => ByteString | The hostname |
| -> Int | The port |
| -> NominalDiffTime | The flood cooldown |
| -> m ConnectionConfig |
Connect to a server without TLS.
Arguments
| :: MonadIO m | |
| => ByteString | The hostname |
| -> Int | The port |
| -> NominalDiffTime | The flood cooldown |
| -> m ConnectionConfig |
Connect to a server with TLS.
start :: MonadIO m => ConnectionConfig -> InstanceConfig -> m () Source
Run the event loop for a server, receiving messages and handing them off to handlers as appropriate. Messages will be logged to stdout.
Logging
The origin of a message.
Constructors
| FromServer | |
| FromClient |
Arguments
| :: MonadIO m | |
| => (Origin -> ByteString -> IO ()) | The message logger |
| -> ByteString | The hostname |
| -> Int | The port |
| -> NominalDiffTime | The flood cooldown |
| -> m ConnectionConfig |
Connect to a server without TLS, with the provided logging function.
Arguments
| :: MonadIO m | |
| => (Origin -> ByteString -> IO ()) | The message logger |
| -> ByteString | The hostname |
| -> Int | The port |
| -> NominalDiffTime | The flood cooldown |
| -> m ConnectionConfig |
Connect to a server with TLS, with the provided logging function.
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.
Interaction
send :: UnicodeMessage -> IRC () Source
Send a message as UTF-8, using TLS if enabled. This blocks if messages are sent too rapidly.
sendBS :: IrcMessage -> IRC () Source
Send a message, using TLS if enabled. This blocks if messages are sent too rapidly.
disconnect :: IRC () Source
Disconnect from the server, properly tearing down the TLS session (if there is one).
Defaults
defaultIRCConf :: Text -> InstanceConfig Source
Construct a default IRC configuration from a nick
defaultDisconnectHandler :: IRC () Source
The default disconnect handler: do nothing. You might want to override this with one which reconnects.
defaultEventHandlers :: [EventHandler] Source
The default event handlers, the following are included:
- respond to server
PINGmessages with aPONG; - respond to CTCP
PINGrequests with a CTCPPONG; - respond to CTCP
VERSIONrequests with the version string; - respond to CTCP
TIMErequests with the system time; - update the nick upon receiving the welcome message, in case the server modifies it;
- mangle the nick if the server reports a collision;
- update the channel list on
JOINandKICK.
These event handlers are all exposed through the
Network.IRC.Client.Handlers module, so you can use them directly if
you are building up your InstanceConfig from scratch.
If you are building a bot, you may want to write an event handler to process messages representing commands.
Types
module Network.IRC.Client.Types
Utilities
module Network.IRC.Client.Utils
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.