stompl-0.6.0: Stomp Parser and Utilities
Copyright(c) Tobias Schoofs
LicenseLGPL
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Network.Mom.Stompl.Frame

Description

Stomp Frames and some useful operations on them

Synopsis

Frames

Frames are the building blocks of the Stomp protocol. They are exchanged between broker and application and contain commands or status and error messages.

Frames follow a simple text-based format. They consist of a command (the FrameType), a list of key/value-pairs, called Header, and a Body (which is empty for most frame types).

data Frame Source #

This is a frame

Instances

Instances details
Eq Frame Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

Methods

(==) :: Frame -> Frame -> Bool #

(/=) :: Frame -> Frame -> Bool #

Show Frame Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

Methods

showsPrec :: Int -> Frame -> ShowS #

show :: Frame -> String #

showList :: [Frame] -> ShowS #

data FrameType Source #

The frame type identifies, what the Stomp protocol calls command;

  • commands sent from application to broker are: Connect, Disconnect, Subscribe, Unsubscribe, Send, Begin, Commit, Abort, Ack, Nack, HeartBeat
  • commands sent from broker to application are: Connected, Message, Error, HeartBeat

Constructors

Connect

Sent by the application to initiate a connection

Stomp

Same as Connect, but with STOMP instead of CONNECT

Connected

Sent by the broker to confirm the connection

Disconnect

Sent by the application to end the connection

Send

Sent by the application to publish a message in a queue

Message

Sent by the broker to forward a message published in a queue to which the application has subscribed

Subscribe

Sent by the application to subscribe to a queue

Unsubscribe

Sent by the application to unsubscribe from a queue

Begin

Sent by the application to start a transaction

Commit

Sent by the application to commit a transaction

Abort

Sent by the application to abort a transaction

Ack

Sent by the application to acknowledge a message

Nack

Sent by the application to negatively acknowledge a message

HeartBeat

Keep-alive message sent by both, application and broker

Error

Sent by the broker to report an error

Receipt

Sent by the broker to confirm the receipt of a frame

Instances

Instances details
Eq FrameType Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

Read FrameType Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

Show FrameType Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

type Header = (String, String) Source #

Tuple of (key, value)

type Body = ByteString Source #

The Frame body is represented as strict ByteString.

type Heart = (Int, Int) Source #

Heart-beat configuration; the first Int of the pair represents the frequency in which the sender wants to send heart-beats; the second represents the highest frequency in which the sender can accept heart-beats. The frequency is expressed as the period in milliseconds between two heart-beats. For details on negotiating heart-beats, please refer to the Stomp specification.

type Version = (Int, Int) Source #

The Stomp version used or accepted by the sender; the first Int is the major version number, the second is the minor. For details on version negotiation, please refer to the Stomp specification.

data AckMode Source #

Constructors

Auto

A successfully sent message is automatically considered ack'd

Client

The client is expected to explicitly confirm the receipt of a message by sending an Ack frame; all message older than the ack'd message since the last Ack (or the beginning of the session) are implicitly ack'd as well. This is called cumulative ack.

ClientIndi

Non-cumulative ack: The client is expected to explicitly confirm the receipt of a message by sending an Ack frame; only the message with the msg-id in the Ack frame is actually ack'd

Instances

Instances details
Eq AckMode Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

Methods

(==) :: AckMode -> AckMode -> Bool #

(/=) :: AckMode -> AckMode -> Bool #

Read AckMode Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

Show AckMode Source # 
Instance details

Defined in Network.Mom.Stompl.Frame

isValidAck :: String -> Bool Source #

check if String represents a valid AckMode

type SrvDesc = (String, String, String) Source #

Description of a server consisting of name, version and comments

getSrvVer :: SrvDesc -> String Source #

get version from SrvDesc

getSrvCmts :: SrvDesc -> String Source #

get comments from SrvDesc

Frame Constructors

There are two different interfaces to construct frames:

  • a set of conventional, basic constructors and
  • a set of header-based constructors

The basic constructors receive the frame attributes directly, i.e. with the types, in which they will be stored. These constructors are, hence, type-safe. They are, however, unsafe in terms of protocol compliance. Headers that identify some entity are stored as plain strings. The basic constructors do not verify if an identifier is required for a given frame type. Using plain strings for identifiers may appear to be odd on the first sight. Since this library is intended for any implementation of Stomp programs (brokers and applications) where identifers (for messages, transactions, receipts, etc.) may have completely different formats, no choice was made on dedicated identifier types.

Header-based constructors, on the other hand, receive attributes packed in a list of Header. The types are converted by the constructor. The constructor, additionally, verfies the protocol compliance. Header-based constructors are, hence, more reliable. This implies, however, that they can fail. For this reason, Header-based constructors return Either.

Basic Frame Constructors

mkConnect :: String -> String -> String -> Heart -> [Version] -> String -> [Header] -> Frame Source #

make a Connect frame (Application -> Broker). The parameters are:

  • User: user to authenticate at the broker.
  • Passcode: password to authenticate at the broker.
  • Host: broker's virtual hoast (e.g. stomp.broker.github.org).
  • HeartBeat: the clients bid in negotiating the heart-beat.
  • Version: the versions supported by the client.
  • ClientId: Client identification for persistent connections. Note that the client id is not a standard Stomp feature, but specific to ActiveMQ and other brokers.
  • Header: List of additional, broker-specific headers

mkStomp :: String -> String -> String -> Heart -> [Version] -> String -> [Header] -> Frame Source #

Same as mkConnect, but the result is a "STOMP" frame rather than a "CONNECT" frame

mkConnected :: String -> Heart -> Version -> SrvDesc -> [Header] -> Frame Source #

make a Connect frame (Broker -> Application). The parameters are:

  • Session: A unique identifier created by the broker and identifying the session
  • HeartBeat: The heart-beat agreed by the broker
  • Version: The version accepted by the broker
  • SrvDesc: The server description
  • Header: List of additional, broker-specific headers.

mkSubscribe :: String -> AckMode -> String -> String -> String -> [Header] -> Frame Source #

make a Subscribe frame (Application -> Broker). The parameters are:

  • Destination: The name of the queue as it is known by the broker and other applications using the queue
  • AckMode: The Acknowledge Mode for this subscription
  • Selector: An expression defining those messages that are of actual for client. The Stomp protocol does not define a language for selectors; it is even not entirely clear, where messages are selected: already at the broker, or only by the client. Some brokers provide pre-selection of messages, others do not.
  • Subscription Id: A unique identifier distinguishing this subscription from others to the same queue. The identifier is defined by the application.
  • Receipt: A unique identifier defined by the application to request confirmation of receipt of this frame. If no receipt is wanted, the string shall be empty.
  • Header: List of additional, broker-specific headers.

mkUnsubscribe :: String -> String -> String -> [Header] -> Frame Source #

make an Unsubscribe frame (Application -> Broker). The parameters are:

  • Destination: The queue name; either a destination or a subscription id must be given. (According to protocol version 1.1, the subscription id is mandatory on both, Subscribe and Unsubscribe.)
  • Subscription Id: The subscription identifier (see mkSubscribe)
  • Receipt: The receipt (see mkSubscribe)
  • Header: Additional, broker-specific headers

mkSend :: String -> String -> String -> Type -> Int -> [Header] -> Body -> Frame Source #

make a Send frame (Application -> Broker). The parameters are:

  • Destination: The name of the queue where the message should be published
  • Transaction: A unique identifier indicating a running transaction; if sent with a transaction, the message will not be delivered to subscribing applications, before the transaction is committed. If the Send is not part of a transaction, the string shall be empty.
  • Receipt: A receipt (see mkSubscribe for details)
  • Type: The content type of the payload message as MIME Type
  • Length: The length of the type in bytes
  • Header: List of additional headers; Stomp protocol requires that user-specified headers are passed through to subscribing applications. These headers may, for instance, be use by selectors to select messages.
  • Body: The payload message

mkMessage :: String -> String -> String -> String -> Type -> Int -> [Header] -> Body -> Frame Source #

make a Message frame (Broker -> Application). The parameters are:

  • Subscription Id: The message was sent because the application subscribed to the queue with this subscription id (see mkSubscribe).
  • Destination: The name of the queue, in wich the message was published.
  • Message Id: A unique message identifier, defined by the broker
  • Type: The type of the playload as MIME Type
  • Length: The length of the payload in bytes
  • Header: A list of user-defined headers (see mkSend for details)
  • Body: The payload

mkErr :: String -> String -> Type -> Int -> [Header] -> Body -> Frame Source #

make a Receipt frame (Broker -> Application). The parameters are:

  • Error Message Id: A short error description
  • Receipt Id: The receipt of frame sent by the application to which this error relates
  • Type: The format of the error message as MIME Type
  • Length: The length of the error message
  • Header: List of additional, broker-specific headers
  • Body: The error message

mkBegin :: String -> String -> [Header] -> Frame Source #

make a Begin frame (Application -> Broker). The parameters are:

  • Transaction: A unique transaction identifier defined by the application.
  • Receipt: A receipt (see mkSubscribe for details)
  • Header: Additional, broker-specific headers

mkCommit :: String -> String -> [Header] -> Frame Source #

make a Commit frame (Application -> Broker). The parameters are:

  • Transaction: A unique transaction identifier defined by the application.
  • Receipt: A receipt (see mkSubscribe for details)
  • Header: Additional, broker-specific headers

mkAbort :: String -> String -> [Header] -> Frame Source #

make an Abort frame (Application -> Broker). The parameters are:

  • Transaction: A unique transaction identifier defined by the application.
  • Receipt: A receipt (see mkSubscribe for details)
  • Header: Additional, broker-specific headers

mkAck :: String -> String -> String -> String -> [Header] -> Frame Source #

make an Ack frame (Application -> Broker). The parameters are:

  • Message Id: The identifier of the message to be ack'd
  • Subscription Id: The subscription, through which the message was received
  • Transaction: Acks may be part of a transaction (see mkSend for details).
  • Receipt: see mkSubscribe for details

mkNack :: String -> String -> String -> String -> [Header] -> Frame Source #

make a Nack frame (Application -> Broker). The parameters are:

  • Message Id: The identifier of the message to be nack'd
  • Subscription Id: The subscription, through which the message was received
  • Transaction: Nacks may be part of a transaction (see mkSend for details).
  • Receipt: see mkSubscribe for details

mkDisconnect :: String -> [Header] -> Frame Source #

make a Disconnect frame (Application -> Broker). The parameter is:

mkBeat :: Frame Source #

make a HeatBeat frame (Application -> Broker and Broker -> Application)

mkReceipt :: String -> [Header] -> Frame Source #

make a Receipt frame (Broker -> Application). The parameter is:

  • Receipt: The receipt identifier received from the application
  • Header: List of additional, broker-specific headers

Header-based Frame Constructors

Working with Headers

mkLogHdr :: String -> Header Source #

make login header

mkPassHdr :: String -> Header Source #

make passcode header

mkDestHdr :: String -> Header Source #

make destination header

mkLenHdr :: String -> Header Source #

make content-length header

mkTrnHdr :: String -> Header Source #

make transaction header

mkRecHdr :: String -> Header Source #

make receipt header

mkSelHdr :: String -> Header Source #

make selector header

mkIdHdr :: String -> Header Source #

make id header (subscribe frame)

mkAckHdr :: String -> Header Source #

make ack header (subscribe frame)

mkSesHdr :: String -> Header Source #

make session header (connected frame)

mkMsgHdr :: String -> Header Source #

make message header (error frame)

mkMIdHdr :: String -> Header Source #

make message-id header

mkAcVerHdr :: String -> Header Source #

make accept-version header (connect frame)

mkVerHdr :: String -> Header Source #

make version header (connected frame)

mkHostHdr :: String -> Header Source #

make host header (connect frame)

mkBeatHdr :: String -> Header Source #

make heart-beat header

mkMimeHdr :: String -> Header Source #

make content-type header

mkSrvHdr :: String -> Header Source #

make server header (connected frame)

mkSubHdr :: String -> Header Source #

make subscription header

mkCliIdHdr :: String -> Header Source #

make client-id header

valToVers :: String -> Maybe [Version] Source #

convert String to list of Version

versToVal :: [Version] -> String Source #

convert list of Version to String

negoVersion :: [Version] -> [Version] -> Version Source #

negotiates version - if no common version is found, the function results in version 1.0!

negoBeat :: Heart -> Heart -> Heart Source #

negotiates heart-beat

rmHdr :: [Header] -> String -> [Header] Source #

remove header (String) from list of Header

rmHdrs :: [Header] -> [String] -> [Header] Source #

remove headers (list of String) from list of Header

Working with Frames

toString :: Frame -> String Source #

converts a Frame into a String

sndToMsg :: String -> String -> String -> Frame -> Maybe Frame Source #

converts a Send frame into a Message frame; parameters:

  • message id
  • subscription id
  • ack id
  • The original Send frame

conToCond :: String -> String -> Heart -> [Version] -> Frame -> Maybe Frame Source #

converts a Connect frame into a Connected frame, negotiating heart-beats and version; parameters:

  • server desc
  • session id
  • caller's bid for heart-beat
  • caller's supported versions
  • the original Connect frame

resetTrans :: Frame -> Frame Source #

sets the transaction header to an empty string; this is a useful function for brokers: when a transaction has been committed, the Send messages can be handled by the same function without, accidentally, iterating into a new transaction.

complies :: Version -> Frame -> Bool Source #

Compliance with protocol version

Get Access to Frames

getDest :: Frame -> String Source #

get destination from Subscribe, Unsubscribe, Send or Message

getTrans :: Frame -> String Source #

get transaction from Send, Ack, Nack, Begin, Commit or Abort

getReceipt :: Frame -> String Source #

get receipt or receipt-id from any frame, but Connect, Connected, Message, Error

getLogin :: Frame -> String Source #

get login from Connect

getPasscode :: Frame -> String Source #

get passcode from Connect

getCliId :: Frame -> String Source #

get client-id from Connect

getHost :: Frame -> String Source #

get host from Connect

getVersions :: Frame -> [Version] Source #

get accept-version from Connect

getVersion :: Frame -> Version Source #

get version from Connected

getBeat :: Frame -> Heart Source #

get heart-beat from Connect or Connected

getSession :: Frame -> String Source #

get session from Connected

getServer :: Frame -> SrvDesc Source #

get server from Connected

getSub :: Frame -> String Source #

get subscription from Ack, Nack or Message

getSelector :: Frame -> String Source #

get selector from Subscribe

getMsgAck :: Frame -> String Source #

get ack or message-id from Message

getMime :: Frame -> Type Source #

get content-type from Send, Message, Error

getLength :: Frame -> Int Source #

get content-length from Send, Message, Error

getMsg :: Frame -> String Source #

get message from Error

getHeaders :: Frame -> [Header] Source #

get all additional headers from Send or Message

Sequence Operators to work on ByteString

(|>) :: ByteString -> Word8 -> ByteString infixr 9 Source #

snoc

(<|) :: Word8 -> ByteString -> ByteString infixr 9 Source #

cons

(>|<) :: ByteString -> ByteString -> ByteString infixr 9 Source #

append

Some random helpers