| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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 stateles 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
- class (NFData (Pdu protocol reply), Show (Pdu protocol reply), Typeable protocol, Typeable reply) => HasPdu (protocol :: Type) (reply :: Synchronicity) where
- data Pdu protocol reply
- deserializePdu :: Dynamic -> Maybe (Pdu protocol reply)
- data Synchronicity
- type family ProtocolReply (s :: Synchronicity) where ...
- type Tangible i = (NFData i, Typeable i, Show i)
- type TangiblePdu p r = (Typeable p, Typeable r, Tangible (Pdu p r))
- newtype Endpoint protocol = Endpoint {}
- fromEndpoint :: forall protocol protocol. Iso (Endpoint protocol) (Endpoint protocol) ProcessId ProcessId
- proxyAsEndpoint :: proxy protocol -> ProcessId -> Endpoint protocol
- asEndpoint :: forall protocol. ProcessId -> Endpoint protocol
- class EmbedProtocol protocol embeddedProtocol (result :: Synchronicity) where
- toEmbeddedEndpoint :: forall inner outer r. EmbedProtocol outer inner r => Endpoint outer -> Endpoint inner
- fromEmbeddedEndpoint :: forall outer inner r. EmbedProtocol outer inner r => Endpoint inner -> Endpoint outer
- prettyTypeableShows :: SomeTypeRep -> ShowS
- prettyTypeableShowsPrec :: Int -> SomeTypeRep -> ShowS
Documentation
class (NFData (Pdu protocol reply), Show (Pdu protocol reply), Typeable protocol, Typeable reply) => HasPdu (protocol :: Type) (reply :: Synchronicity) where 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
instance 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
Minimal complete definition
Nothing
Methods
deserializePdu :: Dynamic -> Maybe (Pdu protocol reply) Source #
deserializePdu :: Typeable (Pdu protocol reply) => Dynamic -> Maybe (Pdu protocol reply) Source #
Instances
| (NFData (Pdu (Sup p) r), Show (Pdu (Sup p) r), Typeable p, Typeable r) => HasPdu (Sup p) r Source # | |
| (Typeable o, Typeable r) => HasPdu (ObserverRegistry o) r Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer Associated Types data Pdu (ObserverRegistry o) r :: Type Source # Methods deserializePdu :: Dynamic -> Maybe (Pdu (ObserverRegistry o) r) Source # | |
| (NFData o, Show o, Typeable o, Typeable r) => HasPdu (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 Since: 0.16.0 |
| (HasPdu a1 r, HasPdu a2 r) => HasPdu (a1, a2) r Source # | |
| (HasPdu a1 r, HasPdu a2 r, HasPdu a3 r) => HasPdu (a1, a2, a3) r Source # | |
| (HasPdu a1 r, HasPdu a2 r, HasPdu a3 r, HasPdu a4 r) => HasPdu (a1, a2, a3, a4) r Source # | |
| (HasPdu a1 r, HasPdu a2 r, HasPdu a3 r, HasPdu a4 r, HasPdu a5 r) => HasPdu (a1, a2, a3, a4, a5) r Source # | |
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. |
| 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 ( or to '()' for an Synchronous t)Pdu x .Asynchronous
Since: 0.24.0
Equations
| ProtocolReply (Synchronous t) = t | |
| ProtocolReply Asynchronous = () |
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 #
Constructors
| Endpoint | |
Fields | |
Instances
| Eq (Endpoint protocol) Source # | |
| Ord (Endpoint protocol) Source # | |
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 # | |
| NFData (Endpoint protocol) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| type ToPretty (Endpoint a :: Type) Source # | |
fromEndpoint :: forall protocol protocol. Iso (Endpoint protocol) (Endpoint protocol) ProcessId ProcessId Source #
proxyAsEndpoint :: proxy protocol -> ProcessId -> Endpoint protocol Source #
asEndpoint :: forall protocol. ProcessId -> Endpoint protocol Source #
class EmbedProtocol protocol embeddedProtocol (result :: Synchronicity) 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 #
embedPdu :: Pdu embeddedProtocol result -> Pdu protocol result Source #
fromPdu :: Pdu protocol result -> Maybe (Pdu embeddedProtocol result) Source #
Instances
| EmbedProtocol a a r Source # | |
| EmbedProtocol (a1, a2) a2 r Source # | |
| EmbedProtocol (a1, a2) a1 r Source # | |
| EmbedProtocol (a1, a2, a3) a3 r Source # | |
| EmbedProtocol (a1, a2, a3) a2 r Source # | |
| EmbedProtocol (a1, a2, a3) a1 r Source # | |
| EmbedProtocol (a1, a2, a3, a4) a4 r Source # | |
| EmbedProtocol (a1, a2, a3, a4) a3 r Source # | |
| EmbedProtocol (a1, a2, a3, a4) a2 r Source # | |
| EmbedProtocol (a1, a2, a3, a4) a1 r Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a5 r Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a4 r Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a3 r Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a2 r Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a1 r Source # | |
toEmbeddedEndpoint :: forall inner outer r. EmbedProtocol outer inner r => Endpoint outer -> Endpoint inner Source #
Convert an Endpoint to an endpoint for an embedded protocol.
See EmbedProtocol, fromEmbeddedEndpoint.
Since: 0.25.1
fromEmbeddedEndpoint :: forall outer inner r. EmbedProtocol outer inner r => Endpoint inner -> Endpoint outer Source #
Convert an Endpoint to an endpoint for a server, that embeds the protocol.
See EmbedProtocol, toEmbeddedEndpoint.
Since: 0.25.1
prettyTypeableShows :: SomeTypeRep -> ShowS Source #
This is equivalent to prettyTypeableShowsPrec 0
Since: 0.24.0
prettyTypeableShowsPrec :: Int -> SomeTypeRep -> ShowS Source #