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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol

Description

Types and functions for type-safe(er) interaction between processes.

All messages sent between processes are eventually converted to Dynamic values which carry little type information.

A step towards a more controlled and type safe process interaction model is done with the facilities defined in this module.

The metaphor for communication is a stateless protocol that describes the messages handled by a process.

A protocol is represented by a custom data type, often a phantom type, which is then used to form specific instances of type classes data/type families, to determine the messages, the replies, the servers and clients, associated with specific task, that needs to be executed concurrently.

This module contains a mechanism to specify what kind of messages (aka requests) an Endpoint can handle.

The Endpoint wraps a ProcessId and carries the protocol phantom-type, to indicate the messages that a process repsonds to.

The associated data type Pdu defines the messages or 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 protocol by using the functions provided by the Control.Eff.Concurrent.Protocol.EffectfulServer and Control.Eff.Concurrent.Protocol.EffectfulServer modules.

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

Synopsis

Documentation

class Typeable protocol => HasPdu (protocol :: Type) Source #

This type class and the associated 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

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

type BookId = Int
type RentalId = Int
type RentalError = String

Since: 0.25.1

Associated Types

type EmbeddedPduList protocol :: [Type] Source #

A type level list Protocol phantom types included in the associated Pdu instance.

This is just a helper for better compiler error messages. It relies on Embeds to add the constraint HasPduPrism.

Since: 0.29.0

data Pdu protocol (reply :: Synchronicity) Source #

The protocol data unit type for the given protocol.

Instances
Tangible event => HasPdu (ObserverRegistry event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (ObserverRegistry event) :: [Type] Source #

data Pdu (ObserverRegistry event) reply :: Type Source #

Typeable p => HasPdu (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

type EmbeddedPduList (Broker p) :: [Type] Source #

data Pdu (Broker p) reply :: Type Source #

Typeable child => HasPdu (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Associated Types

type EmbeddedPduList (Watchdog child) :: [Type] Source #

data Pdu (Watchdog child) reply :: Type Source #

(HasPdu a1, HasPdu a2) => HasPdu (a1, a2) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2) :: [Type] Source #

data Pdu (a1, a2) reply :: Type Source #

Tangible event => HasPdu (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (Observer event) :: [Type] Source #

data Pdu (Observer event) reply :: Type Source #

(HasPdu a1, HasPdu a2, HasPdu a3) => HasPdu (a1, a2, a3) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2, a3) :: [Type] Source #

data Pdu (a1, a2, a3) reply :: Type Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPdu (a1, a2, a3, a4) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2, a3, a4) :: [Type] Source #

data Pdu (a1, a2, a3, a4) reply :: Type Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPdu (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2, a3, a4, a5) :: [Type] Source #

data Pdu (a1, a2, a3, a4, a5) reply :: Type Source #

deserializePdu :: Typeable (Pdu protocol reply) => Dynamic -> Maybe (Pdu protocol reply) Source #

Deserialize a Pdu from a Dynamic i.e. from a message received by a process.

Since: 0.25.1

type Embeds outer inner = (HasPduPrism outer inner, CheckEmbeds outer inner, HasPdu outer) Source #

A constraint that requires that the outer Pdu has a clause to embed values from the inner Pdu.

Also, this constraint requires a HasPduPrism instance, as a proof for a possible conversion of an embedded Pdu value into to the enclosing Pdu.

This generates better compiler error messages, when an embedding of a Pdu into another.

This is provided by HasPdu instances. The instances are required to provide a list of embedded Pdu values in EmbeddedPduList.

Note that every type embeds itself, so Embeds x x always holds.

Since: 0.29.1

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), HasPdu p) 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 #

A server process for protocol.

Protocols are represented by phantom types, which are used in different places to index type families and type class instances.

A Process can send and receive any messages. An Endpoint wraps around a ProcessId and carries a phantom type to indicate the kinds of messages accepted by the process.

As a metaphor, communication between processes can be thought of waiting for and sending protocol data units belonging to some protocol.

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 (Typeable protocol, Typeable embeddedProtocol) => HasPduPrism protocol embeddedProtocol where Source #

A class for Pdu instances that embed other Pdu.

This is a part of Embeds provide instances for your Pdus but in client code use the Embeds constraint.

Instances of this class serve as proof to Embeds that a conversion into another Pdu actually exists.

A Prism for the embedded Pdu is the center of this class

Laws: embeddedPdu = prism' embedPdu fromPdu

Since: 0.29.0

Minimal complete definition

Nothing

Methods

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

A Prism for the embedded Pdus.

embedPdu :: forall (result :: Synchronicity). Pdu embeddedProtocol result -> Pdu protocol result Source #

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

fromPdu :: forall (result :: Synchronicity). Pdu protocol result -> Maybe (Pdu embeddedProtocol result) Source #

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

Instances
Typeable a => HasPduPrism a a Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

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

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

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

Typeable p => HasPduPrism (Broker p) (ObserverRegistry (ChildEvent p)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

embeddedPdu :: Prism' (Pdu (Broker p) result) (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

embedPdu :: Pdu (ObserverRegistry (ChildEvent p)) result -> Pdu (Broker p) result Source #

fromPdu :: Pdu (Broker p) result -> Maybe (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

Typeable child => HasPduPrism (Watchdog child) (Observer (ChildEvent child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

embeddedPdu :: Prism' (Pdu (Watchdog child) result) (Pdu (Observer (ChildEvent child)) result) Source #

embedPdu :: Pdu (Observer (ChildEvent child)) result -> Pdu (Watchdog child) result Source #

fromPdu :: Pdu (Watchdog child) result -> Maybe (Pdu (Observer (ChildEvent child)) result) Source #

(Typeable a1, Typeable a2) => HasPduPrism (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 result -> Pdu (a1, a2) result Source #

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

(Typeable a1, Typeable a2) => HasPduPrism (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 result -> Pdu (a1, a2) result Source #

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

(Typeable a1, Typeable a2, Typeable a3) => HasPduPrism (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 result -> Pdu (a1, a2, a3) result Source #

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

(Typeable a1, Typeable a2, Typeable a3) => HasPduPrism (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 result -> Pdu (a1, a2, a3) result Source #

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

(Typeable a1, Typeable a2, Typeable a3) => HasPduPrism (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 result -> Pdu (a1, a2, a3) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4, a5) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4, a5) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4, a5) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4, a5) result Source #

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

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (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 result -> Pdu (a1, a2, a3, a4, a5) result Source #

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

toEmbeddedEndpoint :: forall inner outer. Embeds outer inner => Endpoint outer -> Endpoint inner Source #

Convert an Endpoint to an endpoint for an embedded protocol.

See Embeds, fromEmbeddedEndpoint.

Since: 0.25.1

fromEmbeddedEndpoint :: forall outer inner. HasPduPrism outer inner => Endpoint inner -> Endpoint outer Source #

Convert an Endpoint to an endpoint for a server, that embeds the protocol.

See Embeds, toEmbeddedEndpoint.

Since: 0.25.1