Portability | portable |
---|---|
Stability | experimental |
Safe Haskell | Safe-Infered |
Network.Mom.Stompl.Frame
Contents
Description
Stomp Frames and some useful operations on them
- data Frame
- data FrameType
- type Header = (String, String)
- type Body = ByteString
- type Heart = (Int, Int)
- type Version = (Int, Int)
- data AckMode
- = Auto
- | Client
- | ClientIndi
- isValidAck :: String -> Bool
- type SrvDesc = (String, String, String)
- getSrvName :: SrvDesc -> String
- getSrvVer :: SrvDesc -> String
- getSrvCmts :: SrvDesc -> String
- mkConnect :: String -> String -> String -> Heart -> [Version] -> Frame
- mkConnected :: String -> Heart -> Version -> SrvDesc -> Frame
- mkSubscribe :: String -> AckMode -> String -> String -> String -> Frame
- mkUnsubscribe :: String -> String -> String -> Frame
- mkSend :: String -> String -> String -> Type -> Int -> [Header] -> Body -> Frame
- mkMessage :: String -> String -> String -> Type -> Int -> [Header] -> Body -> Frame
- mkBegin :: String -> String -> Frame
- mkCommit :: String -> String -> Frame
- mkAbort :: String -> String -> Frame
- mkAck :: String -> String -> String -> String -> Frame
- mkNack :: String -> String -> String -> String -> Frame
- mkDisconnect :: String -> Frame
- mkBeat :: Frame
- mkErr :: String -> String -> Type -> Int -> Body -> Frame
- mkReceipt :: String -> Frame
- mkConFrame :: [Header] -> Either String Frame
- mkCondFrame :: [Header] -> Either String Frame
- mkSubFrame :: [Header] -> Either String Frame
- mkUSubFrame :: [Header] -> Either String Frame
- mkMsgFrame :: [Header] -> Int -> Body -> Either String Frame
- mkSndFrame :: [Header] -> Int -> Body -> Either String Frame
- mkDisFrame :: [Header] -> Either String Frame
- mkErrFrame :: [Header] -> Int -> Body -> Either String Frame
- mkBgnFrame :: [Header] -> Either String Frame
- mkCmtFrame :: [Header] -> Either String Frame
- mkAbrtFrame :: [Header] -> Either String Frame
- mkAckFrame :: [Header] -> Either String Frame
- mkNackFrame :: [Header] -> Either String Frame
- mkRecFrame :: [Header] -> Either String Frame
- mkLogHdr :: String -> Header
- mkPassHdr :: String -> Header
- mkDestHdr :: String -> Header
- mkLenHdr :: String -> Header
- mkTrnHdr :: String -> Header
- mkRecHdr :: String -> Header
- mkSelHdr :: String -> Header
- mkIdHdr :: String -> Header
- mkAckHdr :: String -> Header
- mkSesHdr :: String -> Header
- mkMsgHdr :: String -> Header
- mkMIdHdr :: String -> Header
- mkAcVerHdr :: String -> Header
- mkVerHdr :: String -> Header
- mkHostHdr :: String -> Header
- mkBeatHdr :: String -> Header
- mkMimeHdr :: String -> Header
- mkSrvHdr :: String -> Header
- mkSubHdr :: String -> Header
- valToVer :: String -> Maybe Version
- valToVers :: String -> Maybe [Version]
- verToVal :: Version -> String
- versToVal :: [Version] -> String
- beatToVal :: Heart -> String
- valToBeat :: String -> Maybe Heart
- ackToVal :: AckMode -> String
- valToAck :: String -> Maybe AckMode
- strToSrv :: String -> SrvDesc
- srvToStr :: SrvDesc -> String
- negoVersion :: [Version] -> [Version] -> Version
- negoBeat :: Heart -> Heart -> Heart
- rmHdr :: [Header] -> String -> [Header]
- rmHdrs :: [Header] -> [String] -> [Header]
- getAck :: [Header] -> Either String AckMode
- getLen :: [Header] -> Either String Int
- typeOf :: Frame -> FrameType
- putFrame :: Frame -> ByteString
- toString :: Frame -> String
- putCommand :: Frame -> ByteString
- sndToMsg :: String -> String -> Frame -> Maybe Frame
- conToCond :: String -> String -> Heart -> [Version] -> Frame -> Maybe Frame
- resetTrans :: Frame -> Frame
- complies :: Version -> Frame -> Bool
- getDest :: Frame -> String
- getTrans :: Frame -> String
- getReceipt :: Frame -> String
- getLogin :: Frame -> String
- getPasscode :: Frame -> String
- getHost :: Frame -> String
- getVersions :: Frame -> [Version]
- getVersion :: Frame -> Version
- getBeat :: Frame -> Heart
- getSession :: Frame -> String
- getServer :: Frame -> SrvDesc
- getSub :: Frame -> String
- getSelector :: Frame -> String
- getId :: Frame -> String
- getAcknow :: Frame -> AckMode
- getBody :: Frame -> ByteString
- getMime :: Frame -> Type
- getLength :: Frame -> Int
- getMsg :: Frame -> String
- getHeaders :: Frame -> [Header]
- (|>) :: ByteString -> Char -> ByteString
- (<|) :: Char -> ByteString -> ByteString
- (>|<) :: ByteString -> ByteString -> ByteString
- upString :: String -> String
- numeric :: String -> Bool
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).
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 |
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 |
type Body = ByteStringSource
The Frame body is represented as strict ByteString
.
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.
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 |
ClientIndi | Non-cumulative ack:
The client is expected to explicitly confirm the receipt
of a message by sending an |
type SrvDesc = (String, String, String)Source
Description of a server consisting of name, version and comments
getSrvName :: SrvDesc -> StringSource
get name from SrvDesc
getSrvCmts :: SrvDesc -> StringSource
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] -> FrameSource
make a Connect
frame (Application -> Broker).
The parameters are:
mkSubscribe :: String -> AckMode -> String -> String -> String -> FrameSource
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.
mkUnsubscribe :: String -> String -> String -> FrameSource
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
andUnsubscribe
.) - Subscription Id: The subscription identifier (see
mkSubscribe
) - Receipt: The receipt (see
mkSubscribe
)
mkSend :: String -> String -> String -> Type -> Int -> [Header] -> Body -> FrameSource
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 -> Type -> Int -> [Header] -> Body -> FrameSource
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 (seemkSend
for details) -
Body
: The payload
mkBegin :: String -> String -> FrameSource
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)
mkCommit :: String -> String -> FrameSource
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)
mkAbort :: String -> String -> FrameSource
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)
mkAck :: String -> String -> String -> String -> FrameSource
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 -> FrameSource
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 -> FrameSource
make a Disconnect
frame (Application -> Broker).
The parameter is:
- Receipt: see
mkSubscribe
for details
mkErr :: String -> String -> Type -> Int -> Body -> FrameSource
make a Receipt
frame (Broker -> Application).
The parameters are:
mkReceipt :: String -> FrameSource
make a Receipt
frame (Broker -> Application).
The parameter is:
- Receipt: The receipt identifier received from the application
Header-based Frame Constructors
mkUSubFrame :: [Header] -> Either String FrameSource
make Unsubscribe
frame
mkDisFrame :: [Header] -> Either String FrameSource
make Disconnect
frame
Working with Headers
mkAcVerHdr :: String -> HeaderSource
make accept-version header (connect frame)
negoVersion :: [Version] -> [Version] -> VersionSource
negotiates version - if no common version is found, the function results in version 1.0!
Working with Frames
putFrame :: Frame -> ByteStringSource
converts a Frame
into a ByteString
putCommand :: Frame -> ByteStringSource
converts the FrameType
into a ByteString
resetTrans :: Frame -> FrameSource
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.
Get Access to Frames
getReceipt :: Frame -> StringSource
getPasscode :: Frame -> StringSource
get passcode from Connect
getVersions :: Frame -> [Version]Source
get accept-version from Connect
getVersion :: Frame -> VersionSource
get version from Connected
getSession :: Frame -> StringSource
get session from Connected
getSelector :: Frame -> StringSource
get selector from Subscribe
Sequence Operators to work on ByteString
(|>) :: ByteString -> Char -> ByteStringSource
snoc
(<|) :: Char -> ByteString -> ByteStringSource
cons
(>|<) :: ByteString -> ByteString -> ByteStringSource
append