nqe-0.5.0: Concurrency library in the style of Erlang/OTP

Safe HaskellNone
LanguageHaskell2010

Control.Concurrent.NQE.Process

Synopsis

Documentation

class Eq (mbox msg) => Mailbox mbox msg where Source #

Mailboxes are used to communicate with processes (actors). A process will usually listen in a loop for events entering its mailbox. A process is its mailbox, so it may be named as the process that it communicates with.

>>> :m + Control.Monad NQE UnliftIO
>>> registry <- newTQueueIO :: IO (TQueue String)
>>> let run = receive registry >>= putStrLn . ("Registered: " ++)
>>> withAsync run $ \a -> "Bruce Wayne" `send` registry >> wait a
Registered: Bruce Wayne

Methods

mailboxEmptySTM :: mbox msg -> STM Bool Source #

STM action that responds true if the mailbox is empty. Useful to avoid blocking on an empty mailbox.

mailboxFullSTM :: mbox msg -> STM Bool Source #

STM action that responds true if the mailbox is full and would block if a new message is received.

sendSTM :: msg -> mbox msg -> STM () Source #

STM action to send a message to a mailbox. This is usually called from a process that wishes to communicate with actor that owns the mailbox.

receiveSTM :: mbox msg -> STM msg Source #

STM action to receive a message from a mailbox. This should be called from the process that owns the mailbox.

requeueSTM :: msg -> mbox msg -> STM () Source #

Put a message back in the mailbox so that it is the next one to be received. Used for pattern matching.

Instances
Mailbox TQueue msg Source # 
Instance details

Defined in Control.Concurrent.NQE.Process

Methods

mailboxEmptySTM :: TQueue msg -> STM Bool Source #

mailboxFullSTM :: TQueue msg -> STM Bool Source #

sendSTM :: msg -> TQueue msg -> STM () Source #

receiveSTM :: TQueue msg -> STM msg Source #

requeueSTM :: msg -> TQueue msg -> STM () Source #

Mailbox TBQueue msg Source # 
Instance details

Defined in Control.Concurrent.NQE.Process

Methods

mailboxEmptySTM :: TBQueue msg -> STM Bool Source #

mailboxFullSTM :: TBQueue msg -> STM Bool Source #

sendSTM :: msg -> TBQueue msg -> STM () Source #

receiveSTM :: TBQueue msg -> STM msg Source #

requeueSTM :: msg -> TBQueue msg -> STM () Source #

Mailbox Inbox msg Source # 
Instance details

Defined in Control.Concurrent.NQE.Process

Methods

mailboxEmptySTM :: Inbox msg -> STM Bool Source #

mailboxFullSTM :: Inbox msg -> STM Bool Source #

sendSTM :: msg -> Inbox msg -> STM () Source #

receiveSTM :: Inbox msg -> STM msg Source #

requeueSTM :: msg -> Inbox msg -> STM () Source #

data Inbox msg Source #

Wrapped Mailbox hiding its implementation.

Instances
Mailbox Inbox msg Source # 
Instance details

Defined in Control.Concurrent.NQE.Process

Methods

mailboxEmptySTM :: Inbox msg -> STM Bool Source #

mailboxFullSTM :: Inbox msg -> STM Bool Source #

sendSTM :: msg -> Inbox msg -> STM () Source #

receiveSTM :: Inbox msg -> STM msg Source #

requeueSTM :: msg -> Inbox msg -> STM () Source #

Eq (Inbox msg) Source # 
Instance details

Defined in Control.Concurrent.NQE.Process

Methods

(==) :: Inbox msg -> Inbox msg -> Bool #

(/=) :: Inbox msg -> Inbox msg -> Bool #

Hashable (Inbox msg) Source # 
Instance details

Defined in Control.Concurrent.NQE.Process

Methods

hashWithSalt :: Int -> Inbox msg -> Int #

hash :: Inbox msg -> Int #

type Reply a = a -> STM () Source #

STM action to reply to a synchronous request.

type Listen a = a -> STM () Source #

STM action for an event listener.

newInbox :: (MonadIO m, Mailbox mbox msg) => mbox msg -> m (Inbox msg) Source #

Create a new Inbox with a Unique identifier inside. If you run this function more than once with the same Mailbox, its results will be different from the Eq or Hashable point of view.

send :: (MonadIO m, Mailbox mbox msg) => msg -> mbox msg -> m () Source #

Send a message to a mailbox.

receive :: (MonadIO m, Mailbox mbox msg) => mbox msg -> m msg Source #

Receive a message from the mailbox. This function should be called only by the process that owns the malibox.

query :: (MonadIO m, Mailbox mbox msg) => (Reply a -> msg) -> mbox msg -> m a Source #

Use a partially-applied message type that takes a `Reply a` as its last argument. This function will create the STM action for the response, send the message to a process and await for the STM action to be fulfilled before responding response. It implements synchronous communication with a process.

Example:

>>> :m + NQE UnliftIO
>>> data Message = Square Integer (Reply Integer)
>>> doubler <- newTQueueIO :: IO (TQueue Message)
>>> let proc = receive doubler >>= \(Square i r) -> atomically $ r (i * i)
>>> withAsync proc $ \_ -> Square 2 `query` doubler
4

In this example the Square constructor takes a Reply action as its last argument. It is passed partially-applied to query, which adds a new Reply action before sending it to the doubler and then waiting for it. The doubler process will run the Reply action n STM with the reply as its argument. In this case i * i.

receiveMatch :: (MonadIO m, Mailbox mbox msg) => mbox msg -> (msg -> Maybe a) -> m a Source #

Test all the messages in a mailbox against the supplied function and return the output of the function only when it is Just. Will block until a message matches. All messages that did not match are left in the mailbox. Only call from process that owns mailbox.

receiveMatchSTM :: Mailbox mbox msg => mbox msg -> (msg -> Maybe a) -> STM a Source #

Match a message in the mailbox as an atomic STM action.

mailboxEmpty :: (MonadIO m, Mailbox mbox msg) => mbox msg -> m Bool Source #

Check if the mailbox is empty.