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

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

System.ZMQ4.Monadic

Contents

Description

This modules exposes a monadic interface of ZMQ4. Actions run inside a ZMQ monad and Sockets are guaranteed not to leak outside their corresponding runZMQ scope. Running ZMQ computations asynchronously is directly supported through async.

Synopsis

Type Definitions

data ZMQ z a Source

The ZMQ monad is modeled after ST and encapsulates a Context. It uses the uninstantiated type variable z to distinguish different invoctions of runZMQ and to prevent unintented use of Sockets outside their scope. Cf. the paper of John Launchbury and Simon Peyton Jones Lazy Functional State Threads.

Instances

data Socket z t Source

The ZMQ socket, parameterised by SocketType and belonging to a particular ZMQ thread.

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

Socket type-classes

class Subscriber a Source

Sockets which can subscribe.

Instances

class SocketLike s Source

Minimal complete definition

toSocket

class SendProbe a Source

Sockets which can send probes (cf. setProbeRouter).

Socket Types

data Rep Source

Constructors

Rep 

General Operations

runZMQ :: MonadIO m => (forall z. ZMQ z a) -> m a Source

Return the value computed by the given ZMQ monad. Rank-2 polymorphism is used to prevent leaking of z. An invocation of runZMQ will internally create a Context and all actions are executed relative to this context. On finish the context will be disposed, but see async.

async :: ZMQ z a -> ZMQ z (Async a) Source

Run the given ZMQ computation asynchronously, i.e. this function runs the computation in a new thread using async. N.B. reference counting is used to prolong the lifetime of the Context encapsulated in ZMQ as necessary, e.g.:

runZMQ $ do
    s <- socket Pair
    async $ do
        liftIO (threadDelay 10000000)
        identity s >>= liftIO . print

Here, runZMQ will finish before the code section in async, but due to reference counting, the Context will only be disposed after async finishes as well.

socket :: SocketType t => t -> ZMQ z (Socket z t) Source

ZMQ Options (Read)

ZMQ Options (Write)

Socket operations

close :: Socket z t -> ZMQ z () Source

bind :: Socket z t -> String -> ZMQ z () Source

unbind :: Socket z t -> String -> ZMQ z () Source

connect :: Socket z t -> String -> ZMQ z () Source

disconnect :: Socket z t -> String -> ZMQ z () Source

send :: Sender t => Socket z t -> [Flag] -> ByteString -> ZMQ z () Source

send' :: Sender t => Socket z t -> [Flag] -> ByteString -> ZMQ z () Source

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

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)

Socket Options (Read)

delayAttachOnConnect :: Socket z t -> ZMQ z Bool Source

Deprecated: Use immediate

events :: Socket z t -> ZMQ z [Event] Source

ipv4Only :: Socket z t -> ZMQ z Bool Source

Deprecated: Use ipv6

ipv6 :: Socket z t -> ZMQ z Bool Source

linger :: Socket z t -> ZMQ z Int Source

rate :: Socket z t -> ZMQ z Int Source

Socket Options (Write)

setAffinity :: Word64 -> Socket z t -> ZMQ z () Source

setBacklog :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source

setConflate :: Conflatable t => Bool -> Socket z t -> ZMQ z () Source

setCurveServer :: Bool -> Socket z t -> ZMQ z () Source

setDelayAttachOnConnect :: Bool -> Socket z t -> ZMQ z () Source

Deprecated: Use setImmediate

setImmediate :: Bool -> Socket z t -> ZMQ z () Source

setIpv4Only :: Bool -> Socket z t -> ZMQ z () Source

Deprecated: Use setIpv6

setIpv6 :: Bool -> Socket z t -> ZMQ z () Source

setLinger :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z () Source

setMcastHops :: Integral i => Restricted (N1, Int32) i -> Socket z t -> ZMQ z () Source

setPlainServer :: Bool -> Socket z t -> ZMQ z () Source

setProbeRouter :: SendProbe t => Bool -> Socket z t -> ZMQ z () Source

setRate :: Integral i => Restricted (N1, Int32) i -> Socket z t -> ZMQ z () Source

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.

Re-exports

liftIO :: MonadIO m => forall a. IO a -> m a

Lift a computation from the IO monad.

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.

Low-level Functions

waitRead :: Socket z t -> ZMQ z () Source

waitWrite :: Socket z t -> ZMQ z () Source