nats-queue-0.1.1.0: Haskell API for NATS messaging system

Safe HaskellNone
LanguageHaskell98

Network.Nats

Contents

Synopsis

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 is very sparse. It 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 easily 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. 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 network failure, the nats commands subscribe and request may fail on a network exception. 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.

data Nats Source

Control structure representing a connection to NATS server

connect Source

Arguments

:: String

URI with format: nats://user:password@localhost:4222

-> IO Nats 

Connect to a NATS server

Exceptions

Access

type MsgCallback Source

Arguments

 = NatsSID

SID of subscription

-> String

Subject

-> ByteString

Message

-> Maybe String

Reply subject

-> IO () 

subscribe Source

Arguments

:: Nats 
-> String

Subject

-> Maybe String

Queue

-> MsgCallback

Callback

-> IO NatsSID

SID of subscription

Subscribe to a channel, optionally specifying queue group

unsubscribe :: Nats -> NatsSID -> IO () Source

Unsubscribe from a channel

publish Source

Arguments

:: Nats 
-> String

Subject

-> ByteString

Data

-> IO () 

Publish a message

request Source

Arguments

:: Nats 
-> String

Subject

-> ByteString

Request

-> IO ByteString

Response

Synchronous request/response communication

Termination

disconnect :: Nats -> IO () Source

Disconnect from a NATS server