Safe Haskell | None |
---|---|
Language | Haskell2010 |
Abstractions for the definition of
Command
Messages
, that flow between
Synopsis
- data Message apiTag where
- Blocking :: Show (Command apiTag ('Return result)) => Command apiTag ('Return result) -> ReplyBox result -> Message apiTag
- NonBlocking :: Show (Command apiTag 'FireAndForget) => Command apiTag 'FireAndForget -> Message apiTag
- data family Command apiTag :: ReturnType -> Type
- data ReturnType where
- FireAndForget :: ReturnType
- Return :: Type -> ReturnType
- data ReplyBox a
- data CommandError where
- newtype DuplicateReply = DuplicateReply CallId
- cast :: (MonadUnliftIO m, IsInput o, Show (Command apiTag 'FireAndForget)) => o (Message apiTag) -> Command apiTag 'FireAndForget -> m Bool
- 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)
- replyTo :: MonadUnliftIO m => ReplyBox a -> a -> m ()
- 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))
- delegateCall :: (MonadUnliftIO m, IsInput o, Show (Command apiTag ('Return r))) => o (Message apiTag) -> Command apiTag ('Return r) -> ReplyBox r -> m Bool
- data AsyncReply r
- waitForReply :: MonadUnliftIO m => Int -> AsyncReply result -> m (Either CommandError result)
- tryTakeReply :: MonadUnliftIO m => AsyncReply result -> m (Maybe (Either CommandError result))
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
.
Blocking :: Show (Command apiTag ('Return result)) => Command apiTag ('Return result) -> ReplyBox result -> Message apiTag | Wraps a Such a message can formed by using A |
NonBlocking :: Show (Command apiTag 'FireAndForget) => Command apiTag 'FireAndForget -> Message apiTag | If the The smart constructor |
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.
FireAndForget :: ReturnType | Indicates that a Values of a |
Return :: Type -> ReturnType | Indicates that a Values of a |
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.
CouldNotEnqueueCommand :: !CallId -> CommandError | Failed to enqueue a |
BlockingCommandFailure :: !CallId -> CommandError | The request has failed for reasons. |
BlockingCommandTimedOut :: !CallId -> CommandError | Timeout waiting for the result. |
Instances
Eq CommandError Source # | |
Defined in UnliftIO.MessageBox.Command (==) :: CommandError -> CommandError -> Bool # (/=) :: CommandError -> CommandError -> Bool # | |
Show CommandError Source # | |
Defined in UnliftIO.MessageBox.Command showsPrec :: Int -> CommandError -> ShowS # show :: CommandError -> String # showList :: [CommandError] -> ShowS # |
newtype DuplicateReply Source #
Instances
Eq DuplicateReply Source # | |
Defined in UnliftIO.MessageBox.Command (==) :: DuplicateReply -> DuplicateReply -> Bool # (/=) :: DuplicateReply -> DuplicateReply -> Bool # | |
Show DuplicateReply Source # | |
Defined in UnliftIO.MessageBox.Command showsPrec :: Int -> DuplicateReply -> ShowS # show :: DuplicateReply -> String # showList :: [DuplicateReply] -> ShowS # | |
Exception DuplicateReply Source # | |
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 deliver
y 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 #
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 #
delegateCall :: (MonadUnliftIO m, IsInput o, Show (Command apiTag ('Return r))) => o (Message apiTag) -> Command apiTag ('Return r) -> ReplyBox r -> m Bool Source #
data AsyncReply r Source #
The result of callAsync
.
Use waitForReply
or tryTakeReply
.
Instances
Typeable r => Show (AsyncReply r) Source # | |
Defined in UnliftIO.MessageBox.Command showsPrec :: Int -> AsyncReply r -> ShowS # show :: AsyncReply r -> String # showList :: [AsyncReply r] -> ShowS # |
:: MonadUnliftIO m | |
=> Int | The time in micro seconds to wait
before returning |
-> AsyncReply result | |
-> m (Either CommandError result) |
tryTakeReply :: MonadUnliftIO m => AsyncReply result -> m (Maybe (Either CommandError result)) Source #