| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- data family Pdu (protocol :: Type) (reply :: Synchronicity)
- 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 where
- prettyTypeableShows :: SomeTypeRep -> ShowS
- prettyTypeableShowsPrec :: Int -> SomeTypeRep -> ShowS
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 # | |
| (Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r)) => Show (Pdu (a1, a2, a3) r) Source # | |
| (Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r)) => Show (Pdu (a1, a2, a3, a4) r) Source # | |
| (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 # | |
| Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Supervisor | |
| Show (Pdu (ObserverRegistry o) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer | |
| Show o => Show (Pdu (Observer o) r) Source # | |
| (NFData (Pdu a1 r), NFData (Pdu a2 r)) => NFData (Pdu (a1, a2) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| (NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r)) => NFData (Pdu (a1, a2, a3) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| (NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r)) => NFData (Pdu (a1, a2, a3, a4) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| (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 # | |
Defined in Control.Eff.Concurrent.Protocol | |
| NFData (ChildId p) => NFData (Pdu (Sup p) (Synchronous r)) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Supervisor Methods rnf :: Pdu (Sup p) (Synchronous r) -> () # | |
| NFData (Pdu (ObserverRegistry o) r) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer Methods rnf :: Pdu (ObserverRegistry o) r -> () # | |
| NFData o => NFData (Pdu (Observer o) Asynchronous) Source # | |
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 Since: 0.16.0 |
Defined in Control.Eff.Concurrent.Protocol.Observer data Pdu (Observer o) r where
| |
| type ToPretty (Pdu x y :: Type) Source # | |
| data Pdu (a1, a2) x Source # | |
Defined in Control.Eff.Concurrent.Protocol | |
| data Pdu (Sup p) r Source # | The Since: 0.23.0 |
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 Since: 0.16.0 |
Defined in Control.Eff.Concurrent.Protocol.Observer data Pdu (ObserverRegistry o) r where
| |
| data Pdu (a1, a2, a3) x Source # | |
| data Pdu (a1, a2, a3, a4) x Source # | |
| data Pdu (a1, a2, a3, a4, a5) x 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 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 r -> Pdu protocol r Source #
fromPdu :: Pdu protocol r -> Maybe (Pdu embeddedProtocol r) Source #
Instances
| EmbedProtocol a a Source # | |
| EmbedProtocol (a1, a2) a2 Source # | |
| EmbedProtocol (a1, a2) a1 Source # | |
| EmbedProtocol (a1, a2, a3) a3 Source # | |
| EmbedProtocol (a1, a2, a3) a2 Source # | |
| EmbedProtocol (a1, a2, a3) a1 Source # | |
| EmbedProtocol (a1, a2, a3, a4) a4 Source # | |
| EmbedProtocol (a1, a2, a3, a4) a3 Source # | |
| EmbedProtocol (a1, a2, a3, a4) a2 Source # | |
| EmbedProtocol (a1, a2, a3, a4) a1 Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a5 Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a4 Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a3 Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a2 Source # | |
| EmbedProtocol (a1, a2, a3, a4, a5) a1 Source # | |
prettyTypeableShows :: SomeTypeRep -> ShowS Source #
This is equivalent to prettyTypeableShowsPrec 0
Since: 0.24.0
prettyTypeableShowsPrec :: Int -> SomeTypeRep -> ShowS Source #