extensible-effects-concurrent-0.24.2: 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) => Serializer (Reply protocol reply) -> RequestOrigin protocol reply -> reply -> Eff eff () Source #

Send a Reply to a Call.

The reply will be deeply evaluated to rnf.

To send replies for EmbedProtocol instances use embedReplySerializer.

Since: 0.15.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.24.2-4i89KX4lrqK4F8mqMzm4qM" 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 :: EmbedProtocol outer inner => RequestOrigin inner reply -> RequestOrigin outer reply Source #

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

This function is strict in all parameters.

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.2

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 :: 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 embedRequestOrigin.

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