| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.Nats
Contents
- data Nats
- data NatsSID
- connect :: String -> IO Nats
- connectSettings :: NatsSettings -> IO Nats
- data NatsHost = NatsHost {}
- data NatsSettings = NatsSettings {}
- defaultSettings :: NatsSettings
- data NatsException
- type MsgCallback = NatsSID -> String -> ByteString -> Maybe String -> IO ()
- subscribe :: Nats -> String -> Maybe String -> MsgCallback -> IO NatsSID
- unsubscribe :: Nats -> NatsSID -> IO ()
- publish :: Nats -> String -> ByteString -> IO ()
- request :: Nats -> String -> ByteString -> IO ByteString
- requestMany :: Nats -> String -> ByteString -> Int -> IO [ByteString]
- disconnect :: Nats -> IO ()
How to use this module
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.ByteString.Lazy as BL
nats <- connect "nats://user:password@localhost:4222"
sid <- subscribe nats "news" Nothing $ \_ _ msg _ -> putStrLn $ show msg
publish nats "news" "I got news for you"
unsubscribe nats sid
subscribe nats "gift" Nothing $ \_ _ msg mreply -> do
putStrLn $ show msg
case mreply of
Nothing -> return ()
Just reply -> publish nats reply "I've got a gift for you."
reply <- request nats "gift" "Do you have anything for me?"
putStrLn $ show reply
The connect call connects to the NATS server and creates a receiver thread. The
callbacks are run synchronously on this thread when a server messages comes.
Client commands are generally acknowledged by the server with an +OK message,
the library waits for acknowledgment only for the subscribe command. The NATS
server usually closes the connection when there is an error.
Comparison to API in other languages
Compared to API in other languages, the Haskell binding does
not implement timeouts and automatic unsubscribing, the request call is implemented
as a synchronous call.
The timeouts can be easily implemented using Timeout module, automatic unsubscribing
can be done in the callback function.
Error behaviour
The connect function tries to connect to the NATS server. In case of failure it immediately fails.
If there is an error during operations, the NATS module tries to reconnect to the server.
When there are more servers, the client immediately tries to connect to the next server. If
that fails, it waits 1s before trying the next server in the NatsSettings list.
During the reconnection, the calls subscribe and request will block. The calls
publish and unsubscribe silently fail (unsubscribe is handled locally, NATS is a messaging
system without guarantees, publish is not guaranteed to succeed anyway).
After reconnecting to the server, the module automatically resubscribes to previously subscribed channels.
If there is a network failure, the nats commands subscribe and request
may fail on an IOexception or NatsException. The subscribe
command is synchronous, it waits until the server responds with +OK. The commands publish
and unsubscribe are asynchronous, no confirmation from server is required and they
should not raise an exception.
Connect to a NATS server
connectSettings :: NatsSettings -> IO Nats Source #
Connect to NATS server using custom settings
Host settings; may have different username/password for each host
Constructors
| NatsHost | |
data NatsSettings Source #
Advanced settings for connecting to NATS server
Constructors
| NatsSettings | |
Fields
| |
Exceptions
Access
type MsgCallback Source #
Arguments
| :: Nats | |
| -> String | Subject |
| -> Maybe String | Queue |
| -> MsgCallback | Callback |
| -> IO NatsSID | SID of subscription |
Subscribe to a channel, optionally specifying queue group
Arguments
| :: Nats | |
| -> String | Subject |
| -> ByteString | Request |
| -> IO ByteString | Response |
Synchronous request/response communication to obtain one message
Arguments
| :: Nats | |
| -> String | Subject |
| -> ByteString | Body |
| -> Int | Timeout in microseconds |
| -> IO [ByteString] |
Synchronous request/response for obtaining many messages in certain timespan
Termination
disconnect :: Nats -> IO () Source #
Disconnect from a NATS server