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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol

Description

This module contains a mechanism to specify what kind of messages (aka requests) a Endpoint (Process) can handle, and if the caller blocks and waits for an answer, which the server process provides.

The type magic in the Pdu type family allows to define a related set of requests along with the corresponding responses.

Request handling can be either blocking, if a response is required, or non-blocking.

A process can serve a specific Pdu instance by using the functions provided by the Control.Eff.Concurrent.Pdu.Server module.

To enable a process to use such a service, the functions provided by the Control.Eff.Concurrent.Pdu.Client should be used.

Synopsis

Documentation

data family Pdu (protocol :: Type) (reply :: Synchronicity) Source #

This data family defines the **protocol data units**(PDU) of a protocol.

A Protocol in the sense of a communication interface description between processes.

The first parameter is usually a user defined type that identifies the protocol that uses the Pdus are. It maybe a phantom type.

The second parameter specifies if a specific constructor of an (GADT-like) Pdu instance is Synchronous, i.e. returns a result and blocks the caller or if it is Asynchronous

Example:

data BookShop deriving Typeable

data instance Pdu BookShop r where
  RentBook  :: BookId   -> Pdu BookShop ('Synchronous (Either RentalError RentalId))
  BringBack :: RentalId -> Pdu BookShop 'Asynchronous

type BookId = Int
type RentalId = Int
type RentalError = String
Instances
(Show (Pdu a1 r), Show (Pdu a2 r)) => Show (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2) r -> ShowS #

show :: Pdu (a1, a2) r -> String #

showList :: [Pdu (a1, a2) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r)) => Show (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3) r -> ShowS #

show :: Pdu (a1, a2, a3) r -> String #

showList :: [Pdu (a1, a2, a3) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r)) => Show (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4) r -> ShowS #

show :: Pdu (a1, a2, a3, a4) r -> String #

showList :: [Pdu (a1, a2, a3, a4) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r), Show (Pdu a5 r)) => Show (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4, a5) r -> ShowS #

show :: Pdu (a1, a2, a3, a4, a5) r -> String #

showList :: [Pdu (a1, a2, a3, a4, a5) r] -> ShowS #

Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

showsPrec :: Int -> Pdu (Sup p) (Synchronous r) -> ShowS #

show :: Pdu (Sup p) (Synchronous r) -> String #

showList :: [Pdu (Sup p) (Synchronous r)] -> ShowS #

Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Show o => Show (Pdu (Observer o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer o) r -> ShowS #

show :: Pdu (Observer o) r -> String #

showList :: [Pdu (Observer o) r] -> ShowS #

(NFData (Pdu a1 r), NFData (Pdu a2 r)) => NFData (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r)) => NFData (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r)) => NFData (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r), NFData (Pdu a5 r)) => NFData (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4, a5) r -> () #

NFData (ChildId p) => NFData (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

rnf :: Pdu (Sup p) (Synchronous r) -> () #

NFData (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry o) r -> () #

NFData o => NFData (Pdu (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) Asynchronous -> () #

data Pdu (Observer o) r Source #

A minimal Protocol for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Pdu message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) r where
type ToPretty (Pdu x y :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Pdu x y :: Type) = PrettySurrounded (PutStr "<") (PutStr ">") (("protocol" <:> ToPretty x) <+> ToPretty y)
data Pdu (a1, a2) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) x
data Pdu (Sup p) r Source #

The Pdu instance contains methods to start, stop and lookup a child process, as well as a diagnostic callback.

Since: 0.23.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data Pdu (Sup p) r where
data Pdu (ObserverRegistry o) r Source #

Protocol for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (ObserverRegistry o) r where
data Pdu (a1, a2, a3) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3) x
data Pdu (a1, a2, a3, a4) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4) x
data Pdu (a1, a2, a3, a4, a5) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4, a5) x

data Synchronicity Source #

The (promoted) constructors of this type specify (at the type level) the reply behavior of a specific constructor of an Pdu instance.

Constructors

Synchronous Type

Specify that handling a request is a blocking operation with a specific return type, e.g. ('Synchronous (Either RentalError RentalId))

Asynchronous

Non-blocking, asynchronous, request handling

type family ProtocolReply (s :: Synchronicity) where ... Source #

This type function takes an Pdu and analysis the reply type, i.e. the Synchronicity and evaluates to either t for an Pdu x (Synchronous t) or to '()' for an Pdu x Asynchronous.

Since: 0.24.0

type Tangible i = (NFData i, Typeable i, Show i) Source #

A set of constraints for types that can evaluated via NFData, compared via Ord and presented dynamically via Typeable, and represented both as values via Show.

Since: 0.23.0

type TangiblePdu p r = (Typeable p, Typeable r, Tangible (Pdu p r)) Source #

A Constraint that bundles the requirements for the Pdu values of a protocol.

This ensures that Pdus can be strictly and deeply evaluated and shown such that for example logging is possible.

Since: 0.24.0

newtype Endpoint protocol Source #

This is a tag-type that wraps around a ProcessId and holds an Pdu index type.

Constructors

Endpoint 
Instances
Eq (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

(==) :: Endpoint protocol -> Endpoint protocol -> Bool #

(/=) :: Endpoint protocol -> Endpoint protocol -> Bool #

Ord (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

compare :: Endpoint protocol -> Endpoint protocol -> Ordering #

(<) :: Endpoint protocol -> Endpoint protocol -> Bool #

(<=) :: Endpoint protocol -> Endpoint protocol -> Bool #

(>) :: Endpoint protocol -> Endpoint protocol -> Bool #

(>=) :: Endpoint protocol -> Endpoint protocol -> Bool #

max :: Endpoint protocol -> Endpoint protocol -> Endpoint protocol #

min :: Endpoint protocol -> Endpoint protocol -> Endpoint protocol #

Typeable protocol => Show (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

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

show :: Endpoint protocol -> String #

showList :: [Endpoint protocol] -> ShowS #

NFData (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Endpoint protocol -> () #

type ToPretty (Endpoint a :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Endpoint a :: Type) = ToPretty a <+> PutStr "endpoint"

fromEndpoint :: forall protocol protocol. Iso (Endpoint protocol) (Endpoint protocol) ProcessId ProcessId Source #

proxyAsEndpoint :: proxy protocol -> ProcessId -> Endpoint protocol Source #

Tag a ProcessId with an Pdu type index to mark it a Endpoint process handling that API

asEndpoint :: forall protocol. ProcessId -> Endpoint protocol Source #

Tag a ProcessId with an Pdu type index to mark it a Endpoint process handling that API

class EmbedProtocol protocol embeddedProtocol where Source #

A class for Pdu instances that embed other Pdu. A Prism for the embedded Pdu is the center of this class

Laws: embeddedPdu = prism' embedPdu fromPdu

Since: 0.24.0

Minimal complete definition

Nothing

Methods

embeddedPdu :: Prism' (Pdu protocol result) (Pdu embeddedProtocol result) Source #

A Prism for the embedded Pdus.

embedPdu :: Pdu embeddedProtocol r -> Pdu protocol r Source #

Embed the Pdu value of an embedded protocol into the corresponding Pdu value.

fromPdu :: Pdu protocol r -> Maybe (Pdu embeddedProtocol r) Source #

Examine a Pdu value from the outer protocol, and return it, if it embeds a Pdu of embedded protocol, otherwise return Nothing/

Instances
EmbedProtocol a a Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu a result) (Pdu a result) Source #

embedPdu :: Pdu a r -> Pdu a r Source #

fromPdu :: Pdu a r -> Maybe (Pdu a r) Source #

EmbedProtocol (a1, a2) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2) r Source #

fromPdu :: Pdu (a1, a2) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2) r Source #

fromPdu :: Pdu (a1, a2) r -> Maybe (Pdu a1 r) Source #

EmbedProtocol (a1, a2, a3) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 r -> Pdu (a1, a2, a3) r Source #

fromPdu :: Pdu (a1, a2, a3) r -> Maybe (Pdu a3 r) Source #

EmbedProtocol (a1, a2, a3) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2, a3) r Source #

fromPdu :: Pdu (a1, a2, a3) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2, a3) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2, a3) r Source #

fromPdu :: Pdu (a1, a2, a3) r -> Maybe (Pdu a1 r) Source #

EmbedProtocol (a1, a2, a3, a4) a4 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a4 result) Source #

embedPdu :: Pdu a4 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a4 r) Source #

EmbedProtocol (a1, a2, a3, a4) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a3 r) Source #

EmbedProtocol (a1, a2, a3, a4) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2, a3, a4) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2, a3, a4) r Source #

fromPdu :: Pdu (a1, a2, a3, a4) r -> Maybe (Pdu a1 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a5 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a5 result) Source #

embedPdu :: Pdu a5 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a5 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a4 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a4 result) Source #

embedPdu :: Pdu a4 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a4 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a3 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a2 r) Source #

EmbedProtocol (a1, a2, a3, a4, a5) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 r -> Pdu (a1, a2, a3, a4, a5) r Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) r -> Maybe (Pdu a1 r) Source #

prettyTypeableShows :: SomeTypeRep -> ShowS Source #

This is equivalent to prettyTypeableShowsPrec 0

Since: 0.24.0

prettyTypeableShowsPrec :: Int -> SomeTypeRep -> ShowS Source #

An internal utility to print Typeable without the kinds. This is like showsPrec in that it accepts a precedence parameter, and the result is in parentheses when the precedence is higher than 9.

Since: 0.24.0