| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Concurrent.Protocol.StatefulServer
Contents
Description
Utilities to implement server-loops with builtin state and TEA-like naming.
Since: 0.24.0
Synopsis
- class Typeable (Protocol a) => Server (a :: Type) q where
- data StartArgument a q
- type Protocol a :: Type
- type Model a :: Type
- type Settings a :: Type
- setup :: StartArgument a q -> Eff (Processes q) (Model a, Settings a)
- update :: StartArgument a q -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': Processes q)) ()
- start :: forall a q h. (HasCallStack, Typeable a, LogsTo h (Processes q), Server (Stateful a) (Processes q), Server a q) => StartArgument a q -> Eff (Processes q) (Endpoint (Protocol a))
- startLink :: forall a q h. (HasCallStack, Typeable a, LogsTo h (Processes q), Server (Stateful a) (Processes q), Server a q) => StartArgument a q -> Eff (Processes q) (Endpoint (Protocol a))
- type ModelState a = State (Model a)
- modifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e ()
- getAndModifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a)
- modifyAndGetModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a)
- getModel :: forall a e. Member (ModelState a) e => Eff e (Model a)
- putModel :: forall a e. Member (ModelState a) e => Model a -> Eff e ()
- getAndPutModel :: forall a e. Member (ModelState a) e => Model a -> Eff e (Model a)
- useModel :: forall a b e. Member (ModelState a) e => Getting b (Model a) b -> Eff e b
- zoomModel :: forall a b c e. Member (ModelState a) e => Lens' (Model a) b -> Eff (State b ': e) c -> Eff e c
- type SettingsReader a = Reader (Settings a)
- askSettings :: forall a e. Member (SettingsReader a) e => Eff e (Settings a)
- viewSettings :: forall a b e. Member (SettingsReader a) e => Getting b (Settings a) b -> Eff e b
- data Event a where
- OnCall :: forall a r. (Tangible r, TangiblePdu a (Synchronous r)) => Serializer (Reply a r) -> RequestOrigin a r -> Pdu a (Synchronous r) -> Event a
- OnCast :: forall a. TangiblePdu a Asynchronous => Pdu a Asynchronous -> Event a
- OnInterrupt :: Interrupt Recoverable -> Event a
- OnDown :: ProcessDown -> Event a
- OnTimeOut :: TimerElapsed -> Event a
- OnMessage :: StrictDynamic -> Event a
- data RequestOrigin (proto :: Type) reply = RequestOrigin {}
- data Reply protocol reply where
- sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => Serializer (Reply protocol reply) -> RequestOrigin protocol reply -> reply -> Eff eff ()
- toEmbeddedOrigin :: EmbedProtocol outer inner => RequestOrigin outer reply -> RequestOrigin inner reply
- embedReplySerializer :: EmbedProtocol outer inner => Serializer (Reply outer reply) -> Serializer (Reply inner reply)
Documentation
class Typeable (Protocol a) => Server (a :: Type) q where Source #
A type class for server loops.
This type class serves as interface for other abstractions, for example process supervision
The methods of this class handle Events Requests for Pdu instance.
Instances can by index types for Pdu family directly, or indirectly via the ServerPdu type family.
To builder servers serving multiple protocols, use the generic Pdu instances, for which EmbedProtocol
instances exist, like 2-,3-,4-, or 5-tuple.
The naming is inspired by The Elm Architecture, without the view callback.
This class is based on Control.Eff.Concurrent.Protocol.EffectfulServer and adds a default
State and Reader effect.
Since: 0.24.0
Minimal complete definition
Associated Types
data StartArgument a q Source #
The value that defines what is required to initiate a Server
loop.
type Protocol a :: Type Source #
The index type of the Events that this server processes.
This is the first parameter to the Request and therefore of
the Pdu family.
Type of the model data, given to every invocation of update
via the ModelState effect.
The model of a server loop is changed through incoming Events.
It is initially calculated by setup.
type Settings a :: Type Source #
Type of read-only state.
Methods
setup :: StartArgument a q -> Eff (Processes q) (Model a, Settings a) Source #
setup :: (Default (Model a), Default (Settings a)) => StartArgument a q -> Eff (Processes q) (Model a, Settings a) Source #
update :: StartArgument a q -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': Processes q)) () Source #
Update the Model based on the Event.
Instances
| (TangibleObserver o, TangiblePdu (Observer o) Asynchronous, Lifted IO q, Member Logs q) => Server (ObservationQueue o) q Source # | |
Defined in Control.Eff.Concurrent.Protocol.Observer.Queue Associated Types data StartArgument (ObservationQueue o) q :: Type Source # type Protocol (ObservationQueue o) :: Type Source # type Model (ObservationQueue o) :: Type Source # type Settings (ObservationQueue o) :: Type Source # Methods setup :: StartArgument (ObservationQueue o) q -> Eff (Processes q) (Model (ObservationQueue o), Settings (ObservationQueue o)) Source # update :: StartArgument (ObservationQueue o) q -> Event (Protocol (ObservationQueue o)) -> Eff (ModelState (ObservationQueue o) ': (SettingsReader (ObservationQueue o) ': Processes q)) () Source # | |
| (Lifted IO q, LogsTo IO q, TangibleSup p, Tangible (ChildId p), Server p q) => Server (Sup p) q Source # | |
start :: forall a q h. (HasCallStack, Typeable a, LogsTo h (Processes q), Server (Stateful a) (Processes q), Server a q) => StartArgument a q -> Eff (Processes q) (Endpoint (Protocol a)) Source #
Execute the server loop.
Since: 0.24.0
startLink :: forall a q h. (HasCallStack, Typeable a, LogsTo h (Processes q), Server (Stateful a) (Processes q), Server a q) => StartArgument a q -> Eff (Processes q) (Endpoint (Protocol a)) Source #
Execute the server loop.
Since: 0.24.0
type ModelState a = State (Model a) Source #
modifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e () Source #
getAndModifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a) Source #
modifyAndGetModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a) Source #
getAndPutModel :: forall a e. Member (ModelState a) e => Model a -> Eff e (Model a) Source #
zoomModel :: forall a b c e. Member (ModelState a) e => Lens' (Model a) b -> Eff (State b ': e) c -> Eff e c Source #
type SettingsReader a = Reader (Settings a) Source #
askSettings :: forall a e. Member (SettingsReader a) e => Eff e (Settings a) Source #
viewSettings :: forall a b e. Member (SettingsReader a) e => Getting b (Settings a) b -> Eff e b Source #
Re-exports
Internal protocol to communicate incoming messages and other events to the
instances of Server.
Note that this is required to receive any kind of messages in protocolServerLoop.
Since: 0.24.0
Constructors
| OnCall :: forall a r. (Tangible r, TangiblePdu a (Synchronous r)) => Serializer (Reply a r) -> RequestOrigin a r -> Pdu a (Synchronous r) -> Event a | A Since: 0.24.1 |
| OnCast :: forall a. TangiblePdu a Asynchronous => Pdu a Asynchronous -> Event a | |
| OnInterrupt :: Interrupt Recoverable -> Event a | |
| OnDown :: ProcessDown -> Event a | |
| OnTimeOut :: TimerElapsed -> Event a | |
| OnMessage :: StrictDynamic -> Event a |
data RequestOrigin (proto :: Type) reply Source #
Constructors
| RequestOrigin | |
Fields | |
Instances
data Reply protocol reply where Source #
The wrapper around replies to Calls.
Since: 0.15.0
Constructors
| Reply | |
Fields
| |
sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => Serializer (Reply protocol reply) -> RequestOrigin protocol reply -> reply -> Eff eff () Source #
The reply will be deeply evaluated to rnf.
To send replies for EmbedProtocol instances use embedReplySerializer
and toEmbeddedOrigin.
Since: 0.15.0
toEmbeddedOrigin :: EmbedProtocol outer inner => RequestOrigin outer reply -> RequestOrigin inner reply Source #
Turn an RequestOrigin to an origin for an embedded request (See EmbedProtocol).
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.3
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 toEmbeddedOrigin.
Since: 0.24.2