unliftio-messagebox-2.0.0: Fast and robust message queues for concurrent processes
Safe HaskellNone
LanguageHaskell2010

UnliftIO.MessageBox.Command

Description

Abstractions for the definition of Command Messages, that flow between

Synopsis

Documentation

data Message apiTag where Source #

A message valid for some user defined apiTag.

The apiTag tag (phantom-) type defines the messages allowed here, declared by the instance of Command for apiTag.

Constructors

Blocking :: Show (Command apiTag ('Return result)) => Command apiTag ('Return result) -> ReplyBox result -> Message apiTag

Wraps a Command with a ReturnType of Return result.

Such a message can formed by using call.

A Blocking contains a ReplyBox that can be used to send the reply to the other process blocking on call

NonBlocking :: Show (Command apiTag 'FireAndForget) => Command apiTag 'FireAndForget -> Message apiTag

If the Command has a ReturnType of FireAndForget it has fire-and-forget semantics.

The smart constructor cast can be used to this message.

Instances

Instances details
Show (Message apiTag) Source # 
Instance details

Defined in UnliftIO.MessageBox.Command

Methods

showsPrec :: Int -> Message apiTag -> ShowS #

show :: Message apiTag -> String #

showList :: [Message apiTag] -> ShowS #

data family Command apiTag :: ReturnType -> Type Source #

This family allows to encode imperative commands.

The clauses of a Command define the commands that a process should execute.

Every clause may specify an individual ReturnType that declares if and what response is valid for a message.

For example:

type LampId = Int

data instance Command LightControl r where
  GetLamps :: Command LigthControl (Return [LampId])
  SwitchOn :: LampId -> Command LigthControl FireAndForget

data LightControl -- the phantom type

The type index of the Command family is the uninhabited LightControl type. .

The second type parameter indicates if a message requires the receiver to send a reply back to the blocked and waiting sender, or if no reply is necessary.

data ReturnType where Source #

Indicates if a Command requires the receiver to send a reply or not.

Constructors

FireAndForget :: ReturnType

Indicates that a Command value is sent _one-way_.

Values of a Command instance with FireAndForget as second parameter indicate that the sender should not expect any direct answer from the recepient.

Return :: Type -> ReturnType

Indicates that a Command value requires the receiver to send a reply of the given type.

Values of a Command instance with Return as second parameter are received wrapped into a Blocking.

data ReplyBox a Source #

This is like Input, it can be used by the receiver of a Blocking to either send a reply using reply or to fail/abort the request using sendRequestError

data CommandError where Source #

The failures that the receiver of a Return Command, i.e. a Blocking, can communicate to the caller, in order to indicate that processing a request did not or will not lead to the result the caller is blocked waiting for.

Constructors

CouldNotEnqueueCommand :: !CallId -> CommandError

Failed to enqueue a Blocking Command Message into the corresponding Input

BlockingCommandFailure :: !CallId -> CommandError

The request has failed for reasons.

BlockingCommandTimedOut :: !CallId -> CommandError

Timeout waiting for the result.

Instances

Instances details
Eq CommandError Source # 
Instance details

Defined in UnliftIO.MessageBox.Command

Show CommandError Source # 
Instance details

Defined in UnliftIO.MessageBox.Command

cast :: (MonadUnliftIO m, IsInput o, Show (Command apiTag 'FireAndForget)) => o (Message apiTag) -> Command apiTag 'FireAndForget -> m Bool Source #

Enqueue a NonBlocking Message into an Input. This is just for symetry to call, this is equivalent to: input -> MessageBox.tryToDeliver input . NonBlocking

The

call :: (HasCallIdCounter env, MonadReader env m, MonadUnliftIO m, IsInput input, Show (Command apiTag ('Return result))) => input (Message apiTag) -> Command apiTag ('Return result) -> Int -> m (Either CommandError result) Source #

Enqueue a Blocking Message into an IsInput and wait for the response.

If message delivery failed, return Left CouldNotEnqueueCommand.

If no reply was given by the receiving process (using replyTo) within a given duration, return Left BlockingCommandTimedOut.

Important: The given timeout starts after deliver has returned, if deliver blocks and delays, call might take longer than the specified timeout.

The receiving process can either delegate the call using delegateCall or reply to the call by using: replyTo.

replyTo :: MonadUnliftIO m => ReplyBox a -> a -> m () Source #

This is called from the callback contained in the Blocking Message.

When handling a Blocking Message the ReplyBox contained in the message contains the TMVar for the result, and this function puts the result into it.

callAsync :: (HasCallIdCounter env, MonadReader env m, MonadUnliftIO m, IsInput o, Show (Command apiTag ('Return result))) => o (Message apiTag) -> Command apiTag ('Return result) -> m (Maybe (AsyncReply result)) Source #

Enqueue a Blocking Message into an IsInput.

If the call to deliver fails, return Nothing otherwise Just the AsyncReply.

The receiving process must use replyTo with the ReplyBox received along side the Command in the Blocking.

delegateCall :: (MonadUnliftIO m, IsInput o, Show (Command apiTag ('Return r))) => o (Message apiTag) -> Command apiTag ('Return r) -> ReplyBox r -> m Bool Source #

Pass on the call to another process.

Used to implement dispatcher processes.

Returns True if the deliver operation was successful.

data AsyncReply r Source #

The result of callAsync. Use waitForReply or tryTakeReply.

Instances

Instances details
Typeable r => Show (AsyncReply r) Source # 
Instance details

Defined in UnliftIO.MessageBox.Command

waitForReply Source #

Arguments

:: MonadUnliftIO m 
=> Int

The time in micro seconds to wait before returning Left BlockingCommandTimedOut

-> AsyncReply result 
-> m (Either CommandError result) 

Wait for the reply of a Blocking Message sent by callAsync.

tryTakeReply :: MonadUnliftIO m => AsyncReply result -> m (Maybe (Either CommandError result)) Source #

If a reply for an callAsync operation is available return it, otherwise return Nothing.