zeromq4-haskell-0.8.0: 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

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

Instances details
MonadBaseControl IO (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

liftBaseWith :: (RunInBase (ZMQ z) IO -> IO a) -> ZMQ z a #

restoreM :: StM (ZMQ z) a -> ZMQ z a #

MonadBase IO (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

liftBase :: IO α -> ZMQ z α #

MonadIO (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

liftIO :: IO a -> ZMQ z a #

Applicative (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

pure :: a -> ZMQ z a #

(<*>) :: ZMQ z (a -> b) -> ZMQ z a -> ZMQ z b #

liftA2 :: (a -> b -> c) -> ZMQ z a -> ZMQ z b -> ZMQ z c #

(*>) :: ZMQ z a -> ZMQ z b -> ZMQ z b #

(<*) :: ZMQ z a -> ZMQ z b -> ZMQ z a #

Functor (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

fmap :: (a -> b) -> ZMQ z a -> ZMQ z b #

(<$) :: a -> ZMQ z b -> ZMQ z a #

Monad (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

(>>=) :: ZMQ z a -> (a -> ZMQ z b) -> ZMQ z b #

(>>) :: ZMQ z a -> ZMQ z b -> ZMQ z b #

return :: a -> ZMQ z a #

MonadCatch (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

catch :: (HasCallStack, Exception e) => ZMQ z a -> (e -> ZMQ z a) -> ZMQ z a #

MonadMask (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

mask :: HasCallStack => ((forall a. ZMQ z a -> ZMQ z a) -> ZMQ z b) -> ZMQ z b #

uninterruptibleMask :: HasCallStack => ((forall a. ZMQ z a -> ZMQ z a) -> ZMQ z b) -> ZMQ z b #

generalBracket :: HasCallStack => ZMQ z a -> (a -> ExitCase b -> ZMQ z c) -> (a -> ZMQ z b) -> ZMQ z (b, c) #

MonadThrow (ZMQ z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

throwM :: (HasCallStack, Exception e) => e -> ZMQ z a #

type StM (ZMQ z) a Source # 
Instance details

Defined in System.ZMQ4.Monadic

type StM (ZMQ z) a = a

data Socket z t Source #

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

Instances

Instances details
SocketLike (Socket z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

toSocket :: Socket z t -> Socket t Source #

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

Instances details
Show Flag Source # 
Instance details

Defined in System.ZMQ4.Internal

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Eq Flag Source # 
Instance details

Defined in System.ZMQ4.Internal

Methods

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

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

Ord Flag Source # 
Instance details

Defined in System.ZMQ4.Internal

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

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

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

data Switch Source #

Configuration switch

Constructors

Default

Use default setting

On

Activate setting

Off

De-activate setting

Instances

Instances details
Show Switch Source # 
Instance details

Defined in System.ZMQ4.Internal

Eq Switch Source # 
Instance details

Defined in System.ZMQ4.Internal

Methods

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

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

Ord Switch Source # 
Instance details

Defined in System.ZMQ4.Internal

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

Instances

Instances details
Read Event Source # 
Instance details

Defined in System.ZMQ4

Show Event Source # 
Instance details

Defined in System.ZMQ4

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Ord Event Source # 
Instance details

Defined in System.ZMQ4

Methods

compare :: Event -> Event -> Ordering #

(<) :: Event -> Event -> Bool #

(<=) :: Event -> Event -> Bool #

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

data Poll (s :: Type -> Type) (m :: Type -> Type) 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 :: forall (s :: Type -> Type) t (m :: Type -> Type). s t -> [Event] -> Maybe ([Event] -> m ()) -> Poll s m 
File :: forall (m :: Type -> Type) (s :: Type -> Type). Fd -> [Event] -> Maybe ([Event] -> m ()) -> Poll s m 

data KeyFormat a where Source #

Instances

Instances details
Show (KeyFormat a) Source # 
Instance details

Defined in System.ZMQ4.Internal

Eq (KeyFormat a) Source # 
Instance details

Defined in System.ZMQ4.Internal

Methods

(==) :: KeyFormat a -> KeyFormat a -> Bool #

(/=) :: KeyFormat a -> KeyFormat a -> Bool #

Socket type-classes

class SocketType a Source #

Socket types.

Minimal complete definition

zmqSocketType

Instances

Instances details
SocketType Dealer Source # 
Instance details

Defined in System.ZMQ4

SocketType Pair Source # 
Instance details

Defined in System.ZMQ4

SocketType Pub Source # 
Instance details

Defined in System.ZMQ4

SocketType Pull Source # 
Instance details

Defined in System.ZMQ4

SocketType Push Source # 
Instance details

Defined in System.ZMQ4

SocketType Rep Source # 
Instance details

Defined in System.ZMQ4

SocketType Req Source # 
Instance details

Defined in System.ZMQ4

SocketType Router Source # 
Instance details

Defined in System.ZMQ4

SocketType Stream Source # 
Instance details

Defined in System.ZMQ4

SocketType Sub Source # 
Instance details

Defined in System.ZMQ4

SocketType XPub Source # 
Instance details

Defined in System.ZMQ4

SocketType XSub Source # 
Instance details

Defined in System.ZMQ4

class Sender a Source #

Sockets which can send.

Instances

Instances details
Sender Dealer Source # 
Instance details

Defined in System.ZMQ4

Sender Pair Source # 
Instance details

Defined in System.ZMQ4

Sender Pub Source # 
Instance details

Defined in System.ZMQ4

Sender Push Source # 
Instance details

Defined in System.ZMQ4

Sender Rep Source # 
Instance details

Defined in System.ZMQ4

Sender Req Source # 
Instance details

Defined in System.ZMQ4

Sender Router Source # 
Instance details

Defined in System.ZMQ4

Sender Stream Source # 
Instance details

Defined in System.ZMQ4

Sender XPub Source # 
Instance details

Defined in System.ZMQ4

Sender XSub Source # 
Instance details

Defined in System.ZMQ4

class Receiver a Source #

Sockets which can receive.

Instances

Instances details
Receiver Dealer Source # 
Instance details

Defined in System.ZMQ4

Receiver Pair Source # 
Instance details

Defined in System.ZMQ4

Receiver Pull Source # 
Instance details

Defined in System.ZMQ4

Receiver Rep Source # 
Instance details

Defined in System.ZMQ4

Receiver Req Source # 
Instance details

Defined in System.ZMQ4

Receiver Router Source # 
Instance details

Defined in System.ZMQ4

Receiver Stream Source # 
Instance details

Defined in System.ZMQ4

Receiver Sub Source # 
Instance details

Defined in System.ZMQ4

Receiver XPub Source # 
Instance details

Defined in System.ZMQ4

Receiver XSub Source # 
Instance details

Defined in System.ZMQ4

class Subscriber a Source #

Sockets which can subscribe.

Instances

Instances details
Subscriber Sub Source # 
Instance details

Defined in System.ZMQ4

class SocketLike (s :: Type -> Type) Source #

Minimal complete definition

toSocket

Instances

Instances details
SocketLike Socket Source # 
Instance details

Defined in System.ZMQ4.Internal

Methods

toSocket :: Socket t -> Socket t Source #

SocketLike (Socket z) Source # 
Instance details

Defined in System.ZMQ4.Monadic

Methods

toSocket :: Socket z t -> Socket t Source #

class Conflatable a Source #

Sockets which can be conflated.

Instances

Instances details
Conflatable Dealer Source # 
Instance details

Defined in System.ZMQ4

Conflatable Pub Source # 
Instance details

Defined in System.ZMQ4

Conflatable Pull Source # 
Instance details

Defined in System.ZMQ4

Conflatable Push Source # 
Instance details

Defined in System.ZMQ4

Conflatable Sub Source # 
Instance details

Defined in System.ZMQ4

class SendProbe a Source #

Sockets which can send probes (cf. setProbeRouter).

Instances

Instances details
SendProbe Dealer Source # 
Instance details

Defined in System.ZMQ4

SendProbe Req Source # 
Instance details

Defined in System.ZMQ4

SendProbe Router Source # 
Instance details

Defined in System.ZMQ4

Socket Types

data Pair Source #

Constructors

Pair 

Instances

Instances details
Generic Pair Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Pair 
Instance details

Defined in System.ZMQ4

type Rep Pair = D1 ('MetaData "Pair" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Pair -> Rep Pair x #

to :: Rep Pair x -> Pair #

Eq Pair Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver Pair Source # 
Instance details

Defined in System.ZMQ4

Sender Pair Source # 
Instance details

Defined in System.ZMQ4

SocketType Pair Source # 
Instance details

Defined in System.ZMQ4

type Rep Pair Source # 
Instance details

Defined in System.ZMQ4

type Rep Pair = D1 ('MetaData "Pair" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'False) (U1 :: Type -> Type))

data Pub Source #

Constructors

Pub 

Instances

Instances details
Generic Pub Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Pub 
Instance details

Defined in System.ZMQ4

type Rep Pub = D1 ('MetaData "Pub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Pub" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Pub -> Rep Pub x #

to :: Rep Pub x -> Pub #

Eq Pub Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Conflatable Pub Source # 
Instance details

Defined in System.ZMQ4

Sender Pub Source # 
Instance details

Defined in System.ZMQ4

SocketType Pub Source # 
Instance details

Defined in System.ZMQ4

type Rep Pub Source # 
Instance details

Defined in System.ZMQ4

type Rep Pub = D1 ('MetaData "Pub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Pub" 'PrefixI 'False) (U1 :: Type -> Type))

data Sub Source #

Constructors

Sub 

Instances

Instances details
Generic Sub Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Sub 
Instance details

Defined in System.ZMQ4

type Rep Sub = D1 ('MetaData "Sub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Sub -> Rep Sub x #

to :: Rep Sub x -> Sub #

Eq Sub Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Conflatable Sub Source # 
Instance details

Defined in System.ZMQ4

Receiver Sub Source # 
Instance details

Defined in System.ZMQ4

Subscriber Sub Source # 
Instance details

Defined in System.ZMQ4

SocketType Sub Source # 
Instance details

Defined in System.ZMQ4

type Rep Sub Source # 
Instance details

Defined in System.ZMQ4

type Rep Sub = D1 ('MetaData "Sub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type))

data XPub Source #

Constructors

XPub 

Instances

Instances details
Generic XPub Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep XPub 
Instance details

Defined in System.ZMQ4

type Rep XPub = D1 ('MetaData "XPub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "XPub" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: XPub -> Rep XPub x #

to :: Rep XPub x -> XPub #

Eq XPub Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver XPub Source # 
Instance details

Defined in System.ZMQ4

Sender XPub Source # 
Instance details

Defined in System.ZMQ4

SocketType XPub Source # 
Instance details

Defined in System.ZMQ4

type Rep XPub Source # 
Instance details

Defined in System.ZMQ4

type Rep XPub = D1 ('MetaData "XPub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "XPub" 'PrefixI 'False) (U1 :: Type -> Type))

data XSub Source #

Constructors

XSub 

Instances

Instances details
Generic XSub Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep XSub 
Instance details

Defined in System.ZMQ4

type Rep XSub = D1 ('MetaData "XSub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "XSub" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: XSub -> Rep XSub x #

to :: Rep XSub x -> XSub #

Eq XSub Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver XSub Source # 
Instance details

Defined in System.ZMQ4

Sender XSub Source # 
Instance details

Defined in System.ZMQ4

SocketType XSub Source # 
Instance details

Defined in System.ZMQ4

type Rep XSub Source # 
Instance details

Defined in System.ZMQ4

type Rep XSub = D1 ('MetaData "XSub" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "XSub" 'PrefixI 'False) (U1 :: Type -> Type))

data Req Source #

Constructors

Req 

Instances

Instances details
Generic Req Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Req 
Instance details

Defined in System.ZMQ4

type Rep Req = D1 ('MetaData "Req" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Req" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Req -> Rep Req x #

to :: Rep Req x -> Req #

Eq Req Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver Req Source # 
Instance details

Defined in System.ZMQ4

SendProbe Req Source # 
Instance details

Defined in System.ZMQ4

Sender Req Source # 
Instance details

Defined in System.ZMQ4

SocketType Req Source # 
Instance details

Defined in System.ZMQ4

type Rep Req Source # 
Instance details

Defined in System.ZMQ4

type Rep Req = D1 ('MetaData "Req" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Req" 'PrefixI 'False) (U1 :: Type -> Type))

data Rep Source #

Constructors

Rep 

Instances

Instances details
Generic Rep Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Rep 
Instance details

Defined in System.ZMQ4

type Rep Rep = D1 ('MetaData "Rep" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Rep" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Rep -> Rep Rep x #

to :: Rep Rep x -> Rep #

Eq Rep Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver Rep Source # 
Instance details

Defined in System.ZMQ4

Sender Rep Source # 
Instance details

Defined in System.ZMQ4

SocketType Rep Source # 
Instance details

Defined in System.ZMQ4

type Rep Rep Source # 
Instance details

Defined in System.ZMQ4

type Rep Rep = D1 ('MetaData "Rep" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Rep" 'PrefixI 'False) (U1 :: Type -> Type))

data Dealer Source #

Constructors

Dealer 

Instances

Instances details
Generic Dealer Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Dealer 
Instance details

Defined in System.ZMQ4

type Rep Dealer = D1 ('MetaData "Dealer" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Dealer" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Dealer -> Rep Dealer x #

to :: Rep Dealer x -> Dealer #

Eq Dealer Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Conflatable Dealer Source # 
Instance details

Defined in System.ZMQ4

Receiver Dealer Source # 
Instance details

Defined in System.ZMQ4

SendProbe Dealer Source # 
Instance details

Defined in System.ZMQ4

Sender Dealer Source # 
Instance details

Defined in System.ZMQ4

SocketType Dealer Source # 
Instance details

Defined in System.ZMQ4

type Rep Dealer Source # 
Instance details

Defined in System.ZMQ4

type Rep Dealer = D1 ('MetaData "Dealer" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Dealer" 'PrefixI 'False) (U1 :: Type -> Type))

data Router Source #

Constructors

Router 

Instances

Instances details
Generic Router Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Router 
Instance details

Defined in System.ZMQ4

type Rep Router = D1 ('MetaData "Router" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Router" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Router -> Rep Router x #

to :: Rep Router x -> Router #

Eq Router Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver Router Source # 
Instance details

Defined in System.ZMQ4

SendProbe Router Source # 
Instance details

Defined in System.ZMQ4

Sender Router Source # 
Instance details

Defined in System.ZMQ4

SocketType Router Source # 
Instance details

Defined in System.ZMQ4

type Rep Router Source # 
Instance details

Defined in System.ZMQ4

type Rep Router = D1 ('MetaData "Router" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Router" 'PrefixI 'False) (U1 :: Type -> Type))

data Pull Source #

Constructors

Pull 

Instances

Instances details
Generic Pull Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Pull 
Instance details

Defined in System.ZMQ4

type Rep Pull = D1 ('MetaData "Pull" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Pull" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Pull -> Rep Pull x #

to :: Rep Pull x -> Pull #

Eq Pull Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Conflatable Pull Source # 
Instance details

Defined in System.ZMQ4

Receiver Pull Source # 
Instance details

Defined in System.ZMQ4

SocketType Pull Source # 
Instance details

Defined in System.ZMQ4

type Rep Pull Source # 
Instance details

Defined in System.ZMQ4

type Rep Pull = D1 ('MetaData "Pull" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Pull" 'PrefixI 'False) (U1 :: Type -> Type))

data Push Source #

Constructors

Push 

Instances

Instances details
Generic Push Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Push 
Instance details

Defined in System.ZMQ4

type Rep Push = D1 ('MetaData "Push" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Push" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Push -> Rep Push x #

to :: Rep Push x -> Push #

Eq Push Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Conflatable Push Source # 
Instance details

Defined in System.ZMQ4

Sender Push Source # 
Instance details

Defined in System.ZMQ4

SocketType Push Source # 
Instance details

Defined in System.ZMQ4

type Rep Push Source # 
Instance details

Defined in System.ZMQ4

type Rep Push = D1 ('MetaData "Push" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Push" 'PrefixI 'False) (U1 :: Type -> Type))

data Stream Source #

Constructors

Stream 

Instances

Instances details
Generic Stream Source # 
Instance details

Defined in System.ZMQ4

Associated Types

type Rep Stream 
Instance details

Defined in System.ZMQ4

type Rep Stream = D1 ('MetaData "Stream" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Stream" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Stream -> Rep Stream x #

to :: Rep Stream x -> Stream #

Eq Stream Source # 
Instance details

Defined in System.ZMQ4

Methods

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

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

Receiver Stream Source # 
Instance details

Defined in System.ZMQ4

Sender Stream Source # 
Instance details

Defined in System.ZMQ4

SocketType Stream Source # 
Instance details

Defined in System.ZMQ4

type Rep Stream Source # 
Instance details

Defined in System.ZMQ4

type Rep Stream = D1 ('MetaData "Stream" "System.ZMQ4" "zeromq4-haskell-0.8.0-4TWlySx52LoB8tuO7aoRa1" 'False) (C1 ('MetaCons "Stream" 'PrefixI 'False) (U1 :: Type -> Type))

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 :: forall (s :: Type -> Type) m. (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 #

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 #

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 => IO a -> m a #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

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 #