extensible-effects-concurrent-0.26.1: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.Request

Description

Proxies and containers for casts and calls.

Since: 0.15.0

Synopsis

Documentation

data Request protocol where Source #

A wrapper sum type for calls and casts for the Pdus of a protocol

Since: 0.15.0

Constructors

Call :: forall protocol reply. (Tangible reply, TangiblePdu protocol (Synchronous reply)) => RequestOrigin protocol reply -> Pdu protocol (Synchronous reply) -> Request protocol 
Cast :: forall protocol. (TangiblePdu protocol Asynchronous, NFData (Pdu protocol Asynchronous)) => Pdu protocol Asynchronous -> Request protocol 
Instances
Show (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> Request protocol -> ShowS #

show :: Request protocol -> String #

showList :: [Request protocol] -> ShowS #

NFData (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: Request protocol -> () #

sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => ReplyTarget protocol reply -> reply -> Eff eff () Source #

Answer a Call by sending the reply value to the client process.

The ProcessId, the RequestOrigin and the Reply Serializer are stored in the ReplyTarget.

Since: 0.25.1

newtype ReplyTarget p r Source #

Target of a Call reply.

This combines a RequestOrigin with a Serializer for a Reply using Arg. There are to smart constructors for this type: replyTarget and embeddedReplyTarget.

Because of Arg the Eq and Ord instances are implemented via the RequestOrigin instances.

Since: 0.26.0

Constructors

MkReplyTarget (Arg (RequestOrigin p r) (Serializer (Reply p r))) 
Instances
Eq (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

(==) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(/=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

Ord (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

compare :: ReplyTarget p r -> ReplyTarget p r -> Ordering #

(<) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(<=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(>) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(>=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

max :: ReplyTarget p r -> ReplyTarget p r -> ReplyTarget p r #

min :: ReplyTarget p r -> ReplyTarget p r -> ReplyTarget p r #

Show (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> ReplyTarget p r -> ShowS #

show :: ReplyTarget p r -> String #

showList :: [ReplyTarget p r] -> ShowS #

NFData (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: ReplyTarget p r -> () #

replyTarget :: Serializer (Reply p reply) -> RequestOrigin p reply -> ReplyTarget p reply Source #

Smart constructor for a ReplyTarget.

To build a ReplyTarget for an EmbedProtocol instance use embeddedReplyTarget.

Since: 0.26.0

replyTargetOrigin :: Lens' (ReplyTarget p reply) (RequestOrigin p reply) Source #

A simple Lens for the RequestOrigin of a ReplyTarget.

Since: 0.26.0

replyTargetSerializer :: Lens' (ReplyTarget p reply) (Serializer (Reply p reply)) Source #

A simple Lens for the Reply Serializer of a ReplyTarget.

Since: 0.26.0

embeddedReplyTarget :: EmbedProtocol outer inner => Serializer (Reply outer reply) -> RequestOrigin outer reply -> ReplyTarget inner reply Source #

Smart constructor for an embedded ReplyTarget.

This combines replyTarget and toEmbeddedReplyTarget.

Since: 0.26.0

toEmbeddedReplyTarget :: EmbedProtocol outer inner => ReplyTarget outer r -> ReplyTarget inner r Source #

Convert a ReplyTarget to be usable for embedded replies.

This combines a toEmbeddedOrigin with embedReplySerializer to produce a ReplyTarget that can be passed to functions defined soley on an embedded protocol.

Since: 0.26.0

data RequestOrigin (proto :: Type) reply Source #

Wraps the source ProcessId and a unique identifier for a Call.

Since: 0.15.0

Instances
Eq (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

(==) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(/=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

Ord (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

compare :: RequestOrigin proto reply -> RequestOrigin proto reply -> Ordering #

(<) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(<=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

max :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

min :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

Show (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Generic (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Associated Types

type Rep (RequestOrigin proto reply) :: Type -> Type #

Methods

from :: RequestOrigin proto reply -> Rep (RequestOrigin proto reply) x #

to :: Rep (RequestOrigin proto reply) x -> RequestOrigin proto reply #

NFData (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: RequestOrigin p r -> () #

type Rep (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

type Rep (RequestOrigin proto reply) = D1 (MetaData "RequestOrigin" "Control.Eff.Concurrent.Protocol.Request" "extensible-effects-concurrent-0.26.1-H4MbFpru2ZADB31xfNLjdz" False) (C1 (MetaCons "RequestOrigin" PrefixI True) (S1 (MetaSel (Just "_requestOriginPid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId) :*: S1 (MetaSel (Just "_requestOriginCallRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

embedRequestOrigin :: forall outer inner reply. EmbedProtocol outer inner => RequestOrigin inner reply -> RequestOrigin outer reply Source #

Turn an embedded RequestOrigin to a RequestOrigin for the bigger request.

This is the inverse of toEmbeddedOrigin.

This function is strict in all parameters.

Since: 0.24.2

toEmbeddedOrigin :: forall outer inner reply. EmbedProtocol outer inner => RequestOrigin outer reply -> RequestOrigin inner reply Source #

Turn an RequestOrigin to an origin for an embedded request (See EmbedProtocol).

This is useful of a server delegates the calls and casts for an embedded protocol to functions, that require the Serializer and RequestOrigin in order to call sendReply.

See also embedReplySerializer.

Since: 0.24.3

data Reply protocol reply where Source #

The wrapper around replies to Calls.

Since: 0.15.0

Constructors

Reply 

Fields

Instances
Show r => Show (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> Reply p r -> ShowS #

show :: Reply p r -> String #

showList :: [Reply p r] -> ShowS #

NFData (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: Reply p r -> () #

embedReplySerializer :: forall outer inner reply. EmbedProtocol outer inner => Serializer (Reply outer reply) -> Serializer (Reply inner reply) Source #

Turn a Serializer for a Pdu instance that contains embedded Pdu values into a Reply Serializer for the embedded Pdu.

This is useful of a server delegates the calls and casts for an embedded protocol to functions, that require the Serializer and RequestOrigin in order to call sendReply.

See also toEmbeddedOrigin.

Since: 0.24.2

makeRequestOrigin :: (Typeable r, NFData r, SetMember Process (Process q0) e, '[Interrupts] <:: e) => Eff e (RequestOrigin p r) Source #

Create a new, unique RequestOrigin value for the current process.

Since: 0.24.0