Stomp-0.1: Client library for Stomp brokers.

Network.Stomp

Description

A client library for Stomp serevers implementing stomp 1.1 specification. See http:stomp.github.com/stomp-specification-1.1.html

Example:

import Network.Stomp
import qualified Data.ByteString.Lazy.Char8 as B

main = do
  -- connect to a stomp broker
  con <- connect "stomp://guest:guest@127.0.0.1:61613" vers headers
  putStrLn $ "Accepted versions: " ++ show (versions con)
  
  -- start consumer and subscribe to the queue
  startConsumer con callback
  subscribe con "/queue/test" "0" []

  -- send the messages to the queue
  send con "/queue/test" [] (B.pack "message1")
  send con "/queue/test" [] (B.pack "message2")

  -- wait
  getLine
  
  -- unsubscribe and disconnect
  unsubscribe con "0" []
  disconnect con []
  where 
    vers = [(1,0),(1,1)]
    headers = []

callback :: Frame -> IO ()
callback (Frame (SC MESSAGE) hs body) = do
      putStrLn $ "received message: " ++ (B.unpack body) 
      putStrLn $ "headers: " ++ show hs
callback f = putStrLn $ "received frame: " ++ show f

Synopsis

Documentation

data Command Source

Stomp frame commands

data ServerCommand Source

Broker frame commands

Constructors

CONNECTED 
MESSAGE 
RECEIPT 
ERROR 

data Frame Source

Stomp frame record

Constructors

Frame 

Fields

command :: Command
 
headers :: [Header]
 
body :: ByteString
 

Instances

data Connection Source

A record used to communicate with Stomp brokers

connect :: StompUri -> [Version] -> [Header] -> IO ConnectionSource

connect to the stomp (1.0, 1.1) broker using uri

stomp :: StompUri -> [Header] -> IO ConnectionSource

connect to the stomp 1.1 broker using uri

connect' :: Host -> PortNumber -> [Version] -> [Header] -> IO ConnectionSource

connect to the stomp (1.0, 1.1) broker using hostname and port

stomp' :: Host -> PortNumber -> [Header] -> IO ConnectionSource

connect to the stomp 1.0 broker using hostname and port

disconnect :: Connection -> [Header] -> IO ()Source

closes stomp connection

subscribe :: Connection -> Destination -> Subscription -> [Header] -> IO ()Source

subscribe to the destination to receive stomp frames

unsubscribe :: Connection -> Subscription -> [Header] -> IO ()Source

unsubscribe from destination given the subscription id

ack :: Connection -> Subscription -> MessageId -> [Header] -> IO ()Source

acknowledge the consumption of a message from a subscription

nack :: Connection -> Subscription -> MessageId -> [Header] -> IO ()Source

acknowledge the rejection of a message from a subscription

begin :: Connection -> Transaction -> [Header] -> IO ()Source

start a transaction

commit :: Connection -> Transaction -> [Header] -> IO ()Source

commit a transaction

abort :: Connection -> Transaction -> [Header] -> IO ()Source

rollback a transaction

startConsumer :: Connection -> (Frame -> IO ()) -> IO ()Source

create consume frames thread

receiveFrame :: Connection -> IO FrameSource

reads incoming frame from handle

setExcpHandler :: Connection -> (StompException -> IO ()) -> IO ()Source

set exception handler callback to process the exception in the consumer/heartbeats threads

startSendBeat :: Connection -> IO ()Source

fork send heartbeat thread

startRecvBeat :: Connection -> IO ()Source

fork receive heartbeat thread

sendTimeout :: Connection -> IntSource

send heartbeat timeout

recvTimeout :: Connection -> IntSource

receive heaertbeat timeout

lastSend :: Connection -> MVar UTCTimeSource

last frame sent time

lastRecv :: Connection -> MVar UTCTimeSource

last frame received time

versions :: Connection -> [Version]Source

accepted stomp versions