zeromq4-haskell-0.6: Bindings to ZeroMQ 4.x

Copyright(c) 2010-2013 Toralf Wittner
LicenseMIT
MaintainerToralf Wittner <tw@dtex.org>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell98

System.ZMQ4

Contents

Description

0MQ haskell binding. The API closely follows the C-API of 0MQ with the main difference being that sockets are typed.

Notes

Many option settings use a Restriction to further constrain the range of possible values of their integral types. For example the maximum message size can be given as -1, which means no limit or by greater values, which denote the message size in bytes. The type of setMaxMessageSize is therefore:

setMaxMessageSize :: Integral i
                    => Restricted (Nneg1, Int64) i
                    -> Socket a
                    -> IO ()

which means any integral value in the range of -1 to (maxBound :: Int64) can be given. To create a restricted value from plain value, use toRestricted or restrict.

Synopsis

Type Definitions

Socket Types

data Rep Source

Constructors

Rep 

type XReq = Dealer Source

Deprecated: Use Dealer

type XRep = Router Source

Deprecated: Use Router

Socket type-classes

class Subscriber a Source

Sockets which can subscribe.

Instances

class SocketLike s Source

Minimal complete definition

toSocket

class Conflatable a Source

Sockets which can be conflated.

class SendProbe a Source

Sockets which can send probes (cf. setProbeRouter).

Various type definitions

data Context Source

A 0MQ context representation.

data Socket a Source

A 0MQ Socket.

Instances

data Flag Source

Flags to apply on send operations (cf. man zmq_send)

Constructors

DontWait

ZMQ_DONTWAIT (Only relevant on Windows.)

SendMore

ZMQ_SNDMORE

Instances

data Switch Source

Configuration switch

Constructors

Default

Use default setting

On

Activate setting

Off

De-activate setting

Instances

data Event Source

Socket events.

Constructors

In

ZMQ_POLLIN (incoming messages)

Out

ZMQ_POLLOUT (outgoing messages, i.e. at least 1 byte can be written)

Err
ZMQ_POLLERR

data Poll s m where Source

A Poll value contains the object to poll (a 0MQ socket or a file descriptor), the set of Events which are of interest and--optionally-- a callback-function which is invoked iff the set of interested events overlaps with the actual events.

Constructors

Sock :: s t -> [Event] -> Maybe ([Event] -> m ()) -> Poll s m 
File :: Fd -> [Event] -> Maybe ([Event] -> m ()) -> Poll s m 

data KeyFormat a where Source

Instances

General Operations

withContext :: (Context -> IO a) -> IO a Source

Run an action with a 0MQ context. The Context supplied to your action will not be valid after the action either returns or throws an exception.

withSocket :: SocketType a => Context -> a -> (Socket a -> IO b) -> IO b Source

Run an action with a 0MQ socket. The socket will be closed after running the supplied action even if an error occurs. The socket supplied to your action will not be valid after the action terminates.

bind :: Socket a -> String -> IO () Source

Bind the socket to the given address (cf. zmq_bind).

unbind :: Socket a -> String -> IO () Source

Unbind the socket from the given address (cf. zmq_unbind).

connect :: Socket a -> String -> IO () Source

Connect the socket to the given address (cf. zmq_connect).

disconnect :: Socket a -> String -> IO () Source

Disconnect the socket from the given endpoint (cf. zmq_disconnect).

send :: Sender a => Socket a -> [Flag] -> ByteString -> IO () Source

Send the given ByteString over the socket (cf. zmq_sendmsg).

Note: This function always calls zmq_sendmsg in a non-blocking way, i.e. there is no need to provide the ZMQ_DONTWAIT flag as this is used by default. Still send is blocking the thread as long as the message can not be queued on the socket using GHC's threadWaitWrite.

send' :: Sender a => Socket a -> [Flag] -> ByteString -> IO () Source

Send the given ByteString over the socket (cf. zmq_sendmsg).

This is operationally identical to send socket (Strict.concat (Lazy.toChunks lbs)) flags but may be more efficient.

Note: This function always calls zmq_sendmsg in a non-blocking way, i.e. there is no need to provide the ZMQ_DONTWAIT flag as this is used by default. Still send' is blocking the thread as long as the message can not be queued on the socket using GHC's threadWaitWrite.

sendMulti :: Sender a => Socket a -> NonEmpty ByteString -> IO () Source

Send a multi-part message. This function applies the SendMore Flag between all message parts. 0MQ guarantees atomic delivery of a multi-part message (cf. zmq_sendmsg).

receive :: Receiver a => Socket a -> IO ByteString Source

Receive a ByteString from socket (cf. zmq_recvmsg).

Note: This function always calls zmq_recvmsg in a non-blocking way, i.e. there is no need to provide the ZMQ_DONTWAIT flag as this is used by default. Still receive is blocking the thread as long as no data is available using GHC's threadWaitRead.

receiveMulti :: Receiver a => Socket a -> IO [ByteString] Source

Receive a multi-part message. This function collects all message parts send via sendMulti.

version :: IO (Int, Int, Int) Source

Return the runtime version of the underlying 0MQ library as a (major, minor, patch) triple.

monitor :: [EventType] -> Context -> Socket a -> IO (Bool -> IO (Maybe EventMsg)) Source

Monitor socket events (cf. zmq_socket_monitor).

This function returns a function which can be invoked to retrieve the next socket event, potentially blocking until the next one becomes available. When applied to False, monitoring will terminate, i.e. internal monitoring resources will be disposed. Consequently after monitor has been invoked, the returned function must be applied once to False.

socketMonitor :: [EventType] -> String -> Socket a -> IO () Source

Setup socket monitoring, i.e. a Pair socket which sends monitoring events about the given Socket to the given address.

poll :: (SocketLike s, MonadIO m) => Timeout -> [Poll s m] -> m [[Event]] Source

Polls for events on the given Poll descriptors. Returns a list of events per descriptor which have occured. (cf. zmq_poll)

subscribe :: Subscriber a => Socket a -> ByteString -> IO () Source

Subscribe Socket to given subscription.

unsubscribe :: Subscriber a => Socket a -> ByteString -> IO () Source

Unsubscribe Socket from given subscription.

Context Options (Read)

Context Options (Write)

Socket Options (Read)

conflate :: Conflatable a => Socket a -> IO Bool Source

Restricts the outgoing and incoming socket buffers to a single message.

delayAttachOnConnect :: Socket a -> IO Bool Source

Deprecated: Use immediate

ipv4Only :: Socket a -> IO Bool Source

Deprecated: Use ipv6

Socket Options (Write)

setConflate :: Conflatable a => Bool -> Socket a -> IO () Source

Restrict the outgoing and incoming socket buffers to a single message.

setDelayAttachOnConnect :: Bool -> Socket a -> IO () Source

Deprecated: Use setImmediate

setIpv4Only :: Bool -> Socket a -> IO () Source

Deprecated: Use setIpv6

Restrictions

restrict :: Restriction r v => v -> Restricted r v Source

Create a restricted value. If the given value does not satisfy the restrictions, a modified variant is used instead, e.g. if an integer is larger than the upper bound, the upper bound value is used.

toRestricted :: Restriction r v => v -> Maybe (Restricted r v) Source

Create a restricted value. Returns Nothing if the given value does not satisfy all restrictions.

Error Handling

data ZMQError Source

ZMQError encapsulates information about errors, which occur when using the native 0MQ API, such as error number and message.

errno :: ZMQError -> Int Source

Error number value.

source :: ZMQError -> String Source

Source where this error originates from.

message :: ZMQError -> String Source

Actual error message.

Low-level Functions

init :: Size -> IO Context Source

Deprecated: Use context

term :: Context -> IO () Source

Terminate a 0MQ context. Equivalent to zmq_ctx_term.

shutdown :: Context -> IO () Source

Shutdown a 0MQ context. Equivalent to zmq_ctx_shutdown.

context :: IO Context Source

Initialize a 0MQ context. Equivalent to zmq_ctx_new.

socket :: SocketType a => Context -> a -> IO (Socket a) Source

Create a new 0MQ socket within the given context. withSocket provides automatic socket closing and may be safer to use.

close :: Socket a -> IO () Source

Close a 0MQ socket. withSocket provides automatic socket closing and may be safer to use.

waitRead :: Socket a -> IO () Source

Wait until data is available for reading from the given Socket. After this function returns, a call to receive will essentially be non-blocking.

waitWrite :: Socket a -> IO () Source

Wait until data can be written to the given Socket. After this function returns, a call to send will essentially be non-blocking.

Utils

proxy :: Socket a -> Socket b -> Maybe (Socket c) -> IO () Source

Starts built-in 0MQ proxy (cf. zmq_proxy)

Proxy connects front to back socket

Before calling proxy all sockets should be binded

If the capture socket is not Nothing, the proxy shall send all messages, received on both frontend and backend, to the capture socket.