| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Concurrent.Protocol.StatefulServer
Contents
Description
A better, more safe implementation of the Erlang/OTP gen_server behaviour.
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 (InterruptableProcess q) (Model a, Settings a)
- update :: StartArgument a q -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': InterruptableProcess q)) ()
- start :: forall a q h. (HasCallStack, Typeable a, LogsTo h (InterruptableProcess q), Server (Stateful a) (InterruptableProcess q), Server a q) => StartArgument a q -> Eff (InterruptableProcess q) (Endpoint (Protocol a))
- startLink :: forall a q h. (HasCallStack, Typeable a, LogsTo h (InterruptableProcess q), Server (Stateful a) (InterruptableProcess q), Server a q) => StartArgument a q -> Eff (InterruptableProcess 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 ()
Documentation
class Typeable (Protocol a) => Server (a :: Type) q where Source #
A class for Stateful server processes.
This is inspired by The Elm Architecture, without the view callback.
This can be used for a variety of typical server loop implementations.
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 (InterruptableProcess q) (Model a, Settings a) Source #
setup :: (Default (Model a), Default (Settings a)) => StartArgument a q -> Eff (InterruptableProcess q) (Model a, Settings a) Source #
update :: StartArgument a q -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': InterruptableProcess q)) () Source #
Update the Model based on the Event.
Instances
start :: forall a q h. (HasCallStack, Typeable a, LogsTo h (InterruptableProcess q), Server (Stateful a) (InterruptableProcess q), Server a q) => StartArgument a q -> Eff (InterruptableProcess q) (Endpoint (Protocol a)) Source #
Execute the server loop.
Since: 0.24.0
startLink :: forall a q h. (HasCallStack, Typeable a, LogsTo h (InterruptableProcess q), Server (Stateful a) (InterruptableProcess q), Server a q) => StartArgument a q -> Eff (InterruptableProcess 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
| |