| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Concurrent.Protocol.Server
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) e where
- data StartArgument a e
- type Protocol a :: Type
- type Model a :: Type
- type Settings a :: Type
- setup :: StartArgument a e -> Eff e (Model a, Settings a)
- update :: StartArgument a e -> Event (Protocol a) -> Eff (ToServerEffects a e) ()
- type ToServerEffects a e = ModelState a ': (SettingsReader a ': e)
- 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
- start :: forall a q h. (Server a (InterruptableProcess q), Typeable a, LogsTo h (InterruptableProcess q), HasCallStack) => StartArgument a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (Protocol a))
- startLink :: forall a q h. (Typeable a, Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), HasCallStack) => StartArgument a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (Protocol a))
- protocolServerLoop :: forall q e h a. (Server a e, SetMember Process (Process q) e, Member Interrupts e, LogsTo h e, Typeable a) => StartArgument a e -> Eff e ()
- data GenServer tag e where
- MkGenServer :: LogIo e => {..} -> GenServer tag e
- type ToGenServerEffects tag e = ToServerEffects (GenServer tag e) (InterruptableProcess e)
- newtype GenServerId tag = MkGenServerId {}
- type family GenServerProtocol tag
- type family GenServerModel tag
- type family GenServerSettings tag
- genServer :: forall tag e. (Typeable tag, HasCallStack, LogIo e, Server (GenServer tag e) (InterruptableProcess e)) => (GenServerId tag -> Eff (InterruptableProcess e) (GenServerModel tag, GenServerSettings tag)) -> (GenServerId tag -> Event (GenServerProtocol tag) -> Eff (ToGenServerEffects tag e) ()) -> GenServerId tag -> StartArgument (GenServer tag e) (InterruptableProcess e)
- data Stateless tag
- type ToStatelessEffects e = State () ': (Reader () ': e)
- statelessGenServer :: forall tag e. (Typeable tag, HasCallStack, LogIo e, Typeable tag, Server (GenServer (Stateless tag) e) (InterruptableProcess e)) => (GenServerId tag -> Event (GenServerProtocol tag) -> Eff (ToStatelessEffects (InterruptableProcess e)) ()) -> GenServerId tag -> StartArgument (GenServer (Stateless tag) e) (InterruptableProcess e)
- data Request protocol where
- Call :: forall protocol reply. (Tangible reply, TangiblePdu protocol (Synchronous reply)) => RequestOrigin protocol reply -> Pdu protocol (Synchronous reply) -> Request protocol
- Cast :: forall protocol. TangiblePdu protocol Asynchronous => Pdu protocol Asynchronous -> Request protocol
- sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => RequestOrigin protocol reply -> reply -> Eff eff ()
- data RequestOrigin (proto :: Type) reply = RequestOrigin {}
Documentation
class Typeable (Protocol a) => Server (a :: Type) e where Source #
A type class for Pdu values that have an implementation
which handles the corresponding protocol.
Since: 0.24.0
Minimal complete definition
Associated Types
data StartArgument a e 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 e -> Eff e (Model a, Settings a) Source #
setup :: (Default (Model a), Default (Settings a)) => StartArgument a e -> Eff e (Model a, Settings a) Source #
update :: StartArgument a e -> Event (Protocol a) -> Eff (ToServerEffects a e) () Source #
Instances
type ToServerEffects a e = ModelState a ': (SettingsReader a ': e) Source #
Cons (i.e. prepend) ModelState and SettingsReader to an
effect list.
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 #
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
| OnRequest (Request a) | |
| OnInterrupt (Interrupt Recoverable) | |
| OnDown ProcessDown | |
| OnTimeOut TimerElapsed | |
| OnMessage StrictDynamic |
Instances
start :: forall a q h. (Server a (InterruptableProcess q), Typeable a, LogsTo h (InterruptableProcess q), HasCallStack) => StartArgument a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (Protocol a)) Source #
Execute the server loop.
Since: 0.24.0
startLink :: forall a q h. (Typeable a, Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), HasCallStack) => StartArgument a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (Protocol a)) Source #
Execute the server loop.
Since: 0.24.0
protocolServerLoop :: forall q e h a. (Server a e, SetMember Process (Process q) e, Member Interrupts e, LogsTo h e, Typeable a) => StartArgument a e -> Eff e () Source #
Execute the server loop.
Since: 0.24.0
data GenServer tag e where Source #
A helper for Servers that are directly based on logging and IO: GenIO
A record that contains callbacks to provide a Server instance for the
tag parameter, .
The name prefix Gen indicates the inspiration from Erlang's gen_server module.
Since: 0.24.0
Constructors
| MkGenServer | |
Fields
| |
Instances
type ToGenServerEffects tag e = ToServerEffects (GenServer tag e) (InterruptableProcess e) Source #
Prepend the ModelState for GenServerModel and SettingsReader for GenServerSettings of a GenServer
Server to an effect list.
Since: 0.24.0
newtype GenServerId tag Source #
The name/id of a GenServer for logging purposes.
Since: 0.24.0
Constructors
| MkGenServerId | |
Fields | |
Instances
type family GenServerProtocol tag Source #
The Protocol un-wrapper type function.
Since: 0.24.0
Instances
| type GenServerProtocol (Stateless tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
type family GenServerModel tag Source #
Instances
| type GenServerModel (Stateless tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
type family GenServerSettings tag Source #
Instances
| type GenServerSettings (Stateless tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
genServer :: forall tag e. (Typeable tag, HasCallStack, LogIo e, Server (GenServer tag e) (InterruptableProcess e)) => (GenServerId tag -> Eff (InterruptableProcess e) (GenServerModel tag, GenServerSettings tag)) -> (GenServerId tag -> Event (GenServerProtocol tag) -> Eff (ToGenServerEffects tag e) ()) -> GenServerId tag -> StartArgument (GenServer tag e) (InterruptableProcess e) Source #
Create a GenServer.
This requires the callback for Events, a initial Model and a GenServerId.
There must be a GenServerModel instance.
There must be a GenServerSettings instance.
There must be a GenServerProtocol instance.
This is Haskell, so if this functions is partially applied
to some Event callback, you get a function back,
that generates StartArguments from GenServerIds, like a factory
Since: 0.24.0
The type-level tag indicating a stateless Server instance.
There are GenServerModel, GenServerSettings and GenServerProtocol as well as
ToPretty instances for this type.
See also ToStatelessEffects.
Since: 0.24.0
Instances
| type ToPretty (Stateless t :: Type) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
| type GenServerSettings (Stateless tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
| type GenServerModel (Stateless tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
| type GenServerProtocol (Stateless tag) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Server | |
type ToStatelessEffects e = State () ': (Reader () ': e) Source #
Prepend the ModelState and SettingsReader of a Stateless
Server to an effect list. The Model and Settings of a Stateless
Server are just () unit.
Since: 0.24.0
statelessGenServer :: forall tag e. (Typeable tag, HasCallStack, LogIo e, Typeable tag, Server (GenServer (Stateless tag) e) (InterruptableProcess e)) => (GenServerId tag -> Event (GenServerProtocol tag) -> Eff (ToStatelessEffects (InterruptableProcess e)) ()) -> GenServerId tag -> StartArgument (GenServer (Stateless tag) e) (InterruptableProcess e) Source #
This requires only the callback for Events
and a GenServerId.
This is Haskell, so if this functions is partially applied
to some Event callback, you get a function back,
that generates StartArguments from GenServerIds, like a factory
Since: 0.24.0
Re-exports
data Request protocol where Source #
A wrapper sum type for calls and casts for the Pdus of a protocol
Since: 0.15.0
Constructors
| Call :: forall protocol reply. (Tangible reply, TangiblePdu protocol (Synchronous reply)) => RequestOrigin protocol reply -> Pdu protocol (Synchronous reply) -> Request protocol | |
| Cast :: forall protocol. TangiblePdu protocol Asynchronous => Pdu protocol Asynchronous -> Request protocol |
sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => RequestOrigin protocol reply -> reply -> Eff eff () Source #
data RequestOrigin (proto :: Type) reply Source #
Constructors
| RequestOrigin | |
Fields | |