| Copyright | (c) 2013 Toralf Wittner |
|---|---|
| License | MIT |
| Maintainer | Toralf Wittner <[email protected]> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell98 |
System.ZMQ4.Monadic
Contents
Description
- data ZMQ z a
- data Socket z t
- data Flag
- data Switch
- type Timeout = Int64
- data Event
- data EventType
- data EventMsg
- = Connected !ByteString !Fd
- | ConnectDelayed !ByteString
- | ConnectRetried !ByteString !Int
- | Listening !ByteString !Fd
- | BindFailed !ByteString !Int
- | Accepted !ByteString !Fd
- | AcceptFailed !ByteString !Int
- | Closed !ByteString !Fd
- | CloseFailed !ByteString !Int
- | Disconnected !ByteString !Fd
- | MonitorStopped !ByteString !Int
- data Poll s m where
- data KeyFormat a where
- data SecurityMechanism
- class SocketType a
- class Sender a
- class Receiver a
- class Subscriber a
- class SocketLike s
- class Conflatable a
- class SendProbe a
- data Pair = Pair
- data Pub = Pub
- data Sub = Sub
- data XPub = XPub
- data XSub = XSub
- data Req = Req
- data Rep = Rep
- data Dealer = Dealer
- data Router = Router
- data Pull = Pull
- data Push = Push
- data Stream = Stream
- version :: ZMQ z (Int, Int, Int)
- runZMQ :: MonadIO m => (forall z. ZMQ z a) -> m a
- async :: ZMQ z a -> ZMQ z (Async a)
- socket :: SocketType t => t -> ZMQ z (Socket z t)
- ioThreads :: ZMQ z Word
- maxSockets :: ZMQ z Word
- setIoThreads :: Word -> ZMQ z ()
- setMaxSockets :: Word -> ZMQ z ()
- close :: Socket z t -> ZMQ z ()
- bind :: Socket z t -> String -> ZMQ z ()
- unbind :: Socket z t -> String -> ZMQ z ()
- connect :: Socket z t -> String -> ZMQ z ()
- disconnect :: Socket z t -> String -> ZMQ z ()
- send :: Sender t => Socket z t -> [Flag] -> ByteString -> ZMQ z ()
- send' :: Sender t => Socket z t -> [Flag] -> ByteString -> ZMQ z ()
- sendMulti :: Sender t => Socket z t -> NonEmpty ByteString -> ZMQ z ()
- receive :: Receiver t => Socket z t -> ZMQ z ByteString
- receiveMulti :: Receiver t => Socket z t -> ZMQ z [ByteString]
- subscribe :: Subscriber t => Socket z t -> ByteString -> ZMQ z ()
- unsubscribe :: Subscriber t => Socket z t -> ByteString -> ZMQ z ()
- proxy :: Socket z a -> Socket z b -> Maybe (Socket z c) -> ZMQ z ()
- monitor :: [EventType] -> Socket z t -> ZMQ z (Bool -> IO (Maybe EventMsg))
- socketMonitor :: [EventType] -> String -> Socket z t -> ZMQ z ()
- poll :: (SocketLike s, MonadIO m) => Timeout -> [Poll s m] -> m [[Event]]
- affinity :: Socket z t -> ZMQ z Word64
- backlog :: Socket z t -> ZMQ z Int
- conflate :: Conflatable t => Socket z t -> ZMQ z Bool
- curvePublicKey :: KeyFormat f -> Socket z t -> ZMQ z ByteString
- curveSecretKey :: KeyFormat f -> Socket z t -> ZMQ z ByteString
- curveServerKey :: KeyFormat f -> Socket z t -> ZMQ z ByteString
- delayAttachOnConnect :: Socket z t -> ZMQ z Bool
- events :: Socket z t -> ZMQ z [Event]
- fileDescriptor :: Socket z t -> ZMQ z Fd
- identity :: Socket z t -> ZMQ z ByteString
- immediate :: Socket z t -> ZMQ z Bool
- ipv4Only :: Socket z t -> ZMQ z Bool
- ipv6 :: Socket z t -> ZMQ z Bool
- lastEndpoint :: Socket z t -> ZMQ z String
- linger :: Socket z t -> ZMQ z Int
- maxMessageSize :: Socket z t -> ZMQ z Int64
- mcastHops :: Socket z t -> ZMQ z Int
- mechanism :: Socket z t -> ZMQ z SecurityMechanism
- moreToReceive :: Socket z t -> ZMQ z Bool
- plainServer :: Socket z t -> ZMQ z Bool
- plainPassword :: Socket z t -> ZMQ z ByteString
- plainUserName :: Socket z t -> ZMQ z ByteString
- rate :: Socket z t -> ZMQ z Int
- receiveBuffer :: Socket z t -> ZMQ z Int
- receiveHighWM :: Socket z t -> ZMQ z Int
- receiveTimeout :: Socket z t -> ZMQ z Int
- reconnectInterval :: Socket z t -> ZMQ z Int
- reconnectIntervalMax :: Socket z t -> ZMQ z Int
- recoveryInterval :: Socket z t -> ZMQ z Int
- sendBuffer :: Socket z t -> ZMQ z Int
- sendHighWM :: Socket z t -> ZMQ z Int
- sendTimeout :: Socket z t -> ZMQ z Int
- tcpKeepAlive :: Socket z t -> ZMQ z Switch
- tcpKeepAliveCount :: Socket z t -> ZMQ z Int
- tcpKeepAliveIdle :: Socket z t -> ZMQ z Int
- tcpKeepAliveInterval :: Socket z t -> ZMQ z Int
- zapDomain :: Socket z t -> ZMQ z ByteString
- setAffinity :: Word64 -> Socket z t -> ZMQ z ()
- setBacklog :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setConflate :: Conflatable t => Bool -> Socket z t -> ZMQ z ()
- setCurveServer :: Bool -> Socket z t -> ZMQ z ()
- setCurvePublicKey :: KeyFormat f -> Restricted f ByteString -> Socket z t -> ZMQ z ()
- setCurveSecretKey :: KeyFormat f -> Restricted f ByteString -> Socket z t -> ZMQ z ()
- setCurveServerKey :: KeyFormat f -> Restricted f ByteString -> Socket z t -> ZMQ z ()
- setDelayAttachOnConnect :: Bool -> Socket z t -> ZMQ z ()
- setIdentity :: Restricted (N1, N254) ByteString -> Socket z t -> ZMQ z ()
- setImmediate :: Bool -> Socket z t -> ZMQ z ()
- setIpv4Only :: Bool -> Socket z t -> ZMQ z ()
- setIpv6 :: Bool -> Socket z t -> ZMQ z ()
- setLinger :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z ()
- setMaxMessageSize :: Integral i => Restricted (Nneg1, Int64) i -> Socket z t -> ZMQ z ()
- setMcastHops :: Integral i => Restricted (N1, Int32) i -> Socket z t -> ZMQ z ()
- setPlainServer :: Bool -> Socket z t -> ZMQ z ()
- setPlainPassword :: Restricted (N1, N254) ByteString -> Socket z t -> ZMQ z ()
- setPlainUserName :: Restricted (N1, N254) ByteString -> Socket z t -> ZMQ z ()
- setProbeRouter :: SendProbe t => Bool -> Socket z t -> ZMQ z ()
- setRate :: Integral i => Restricted (N1, Int32) i -> Socket z t -> ZMQ z ()
- setReceiveBuffer :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setReceiveHighWM :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setReceiveTimeout :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z ()
- setReconnectInterval :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setReconnectIntervalMax :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setRecoveryInterval :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setReqCorrelate :: Bool -> Socket z Req -> ZMQ z ()
- setReqRelaxed :: Bool -> Socket z Req -> ZMQ z ()
- setRouterMandatory :: Bool -> Socket z Router -> ZMQ z ()
- setSendBuffer :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setSendHighWM :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z ()
- setSendTimeout :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z ()
- setTcpAcceptFilter :: Maybe ByteString -> Socket z t -> ZMQ z ()
- setTcpKeepAlive :: Switch -> Socket z t -> ZMQ z ()
- setTcpKeepAliveCount :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z ()
- setTcpKeepAliveIdle :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z ()
- setTcpKeepAliveInterval :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z ()
- setXPubVerbose :: Bool -> Socket z XPub -> ZMQ z ()
- data ZMQError
- errno :: ZMQError -> Int
- source :: ZMQError -> String
- message :: ZMQError -> String
- liftIO :: MonadIO m => forall a. IO a -> m a
- restrict :: Restriction r v => v -> Restricted r v
- toRestricted :: Restriction r v => v -> Maybe (Restricted r v)
- waitRead :: Socket z t -> ZMQ z ()
- waitWrite :: Socket z t -> ZMQ z ()
- z85Encode :: MonadIO m => Restricted Div4 ByteString -> m ByteString
- z85Decode :: MonadIO m => Restricted Div5 ByteString -> m ByteString
- curveKeyPair :: MonadIO m => m (Restricted Div5 ByteString, Restricted Div5 ByteString)
Type Definitions
The ZMQ socket, parameterised by SocketType and belonging to
a particular ZMQ thread.
Instances
| SocketLike (Socket z) Source # | |
Flags to apply on send operations (cf. man zmq_send)
Configuration switch
Socket events.
Event types to monitor.
Event Message to receive when monitoring socket events.
Constructors
data KeyFormat a where Source #
Constructors
| BinaryFormat :: KeyFormat Div4 | |
| TextFormat :: KeyFormat Div5 |
data SecurityMechanism Source #
Instances
Socket type-classes
class SocketType a Source #
Socket types.
Minimal complete definition
Instances
Sockets which can send.
Sockets which can receive.
Sockets which can send probes (cf. setProbeRouter).
Socket Types
Constructors
| Pair |
Constructors
| Pub |
Constructors
| Sub |
Constructors
| XPub |
Constructors
| XSub |
Constructors
| Req |
Constructors
| Rep |
Constructors
| Dealer |
Constructors
| Router |
Constructors
| Pull |
Constructors
| Push |
Constructors
| Stream |
General Operations
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.
ZMQ Options (Read)
maxSockets :: ZMQ z Word Source #
ZMQ Options (Write)
setIoThreads :: Word -> ZMQ z () Source #
setMaxSockets :: Word -> ZMQ z () Source #
Socket operations
receiveMulti :: Receiver t => Socket z t -> ZMQ z [ByteString] Source #
subscribe :: Subscriber t => Socket z t -> ByteString -> ZMQ z () Source #
unsubscribe :: Subscriber t => Socket z t -> ByteString -> ZMQ z () Source #
Socket Options (Read)
curvePublicKey :: KeyFormat f -> Socket z t -> ZMQ z ByteString Source #
curveSecretKey :: KeyFormat f -> Socket z t -> ZMQ z ByteString Source #
curveServerKey :: KeyFormat f -> Socket z t -> ZMQ z ByteString Source #
plainPassword :: Socket z t -> ZMQ z ByteString Source #
plainUserName :: Socket z t -> ZMQ z ByteString Source #
Socket Options (Write)
setBacklog :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setConflate :: Conflatable t => Bool -> Socket z t -> ZMQ z () Source #
setCurvePublicKey :: KeyFormat f -> Restricted f ByteString -> Socket z t -> ZMQ z () Source #
setCurveSecretKey :: KeyFormat f -> Restricted f ByteString -> Socket z t -> ZMQ z () Source #
setCurveServerKey :: KeyFormat f -> Restricted f ByteString -> Socket z t -> ZMQ z () Source #
setIdentity :: Restricted (N1, N254) ByteString -> Socket z t -> ZMQ z () Source #
setMaxMessageSize :: Integral i => Restricted (Nneg1, Int64) i -> Socket z t -> ZMQ z () Source #
setMcastHops :: Integral i => Restricted (N1, Int32) i -> Socket z t -> ZMQ z () Source #
setPlainPassword :: Restricted (N1, N254) ByteString -> Socket z t -> ZMQ z () Source #
setPlainUserName :: Restricted (N1, N254) ByteString -> Socket z t -> ZMQ z () Source #
setReceiveBuffer :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setReceiveHighWM :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setReceiveTimeout :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z () Source #
setReconnectInterval :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setReconnectIntervalMax :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setRecoveryInterval :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setSendBuffer :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setSendHighWM :: Integral i => Restricted (N0, Int32) i -> Socket z t -> ZMQ z () Source #
setSendTimeout :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z () Source #
setTcpAcceptFilter :: Maybe ByteString -> Socket z t -> ZMQ z () Source #
setTcpKeepAliveCount :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z () Source #
setTcpKeepAliveIdle :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z () Source #
setTcpKeepAliveInterval :: Integral i => Restricted (Nneg1, Int32) i -> Socket z t -> ZMQ z () Source #
Error Handling
ZMQError encapsulates information about errors, which occur when using the native 0MQ API, such as error number and message.
Re-exports
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
z85Encode :: MonadIO m => Restricted Div4 ByteString -> m ByteString Source #
z85Decode :: MonadIO m => Restricted Div5 ByteString -> m ByteString Source #
curveKeyPair :: MonadIO m => m (Restricted Div5 ByteString, Restricted Div5 ByteString) Source #
Generate a new curve key pair. (cf. zmq_curve_keypair)