| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Concurrent.Protocol.EffectfulServer
Contents
Description
A better, more safe implementation of the Erlang/OTP gen_server behaviour.
Since: 0.24.0
Synopsis
- class Server (a :: Type) (e :: [Type -> Type]) where
- 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
- start :: forall a q h. (Server a (InterruptableProcess q), Typeable a, Typeable (ServerPdu a), LogsTo h (InterruptableProcess q), SetMember Process (Process q) (Effects a (InterruptableProcess q)), Member Interrupts (Effects a (InterruptableProcess q)), HasCallStack) => Init a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (ServerPdu a))
- startLink :: forall a q h. (Typeable a, Typeable (ServerPdu a), Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), SetMember Process (Process q) (Effects a (InterruptableProcess q)), Member Interrupts (Effects a (InterruptableProcess q)), HasCallStack) => Init a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (ServerPdu a))
- protocolServerLoop :: forall q h a. (Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), SetMember Process (Process q) (Effects a (InterruptableProcess q)), Member Interrupts (Effects a (InterruptableProcess q)), Typeable a, Typeable (ServerPdu a)) => Init a (InterruptableProcess q) -> Eff (InterruptableProcess q) ()
- type TangibleGenServer tag eLoop e = (LogIo e, SetMember Process (Process e) eLoop, Member Interrupts eLoop, Typeable e, Typeable eLoop, Typeable tag)
- data GenServer tag eLoop e
- newtype GenServerId tag = MkGenServerId {}
- genServer :: forall tag eLoop e. (HasCallStack, TangibleGenServer tag eLoop e, Server (GenServer tag eLoop e) (InterruptableProcess e)) => (forall x. GenServerId tag -> Eff eLoop x -> Eff (InterruptableProcess e) x) -> (GenServerId tag -> Event tag -> Eff eLoop ()) -> GenServerId tag -> Init (GenServer tag eLoop e) (InterruptableProcess e)
- 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 Server (a :: Type) (e :: [Type -> Type]) where Source #
A type class for building supervised processes, that handle Events
with Requests for Pdu instance.
Since: 0.24.1
Minimal complete definition
Nothing
Associated Types
The value that defines what is required to initiate a Server
loop.
type ServerPdu 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 Effects a e :: [Type -> Type] Source #
Effects of the implementation
Since: 0.24.1
Methods
serverTitle :: Init a e -> ProcessTitle Source #
Return the ProcessTitle.
Usually you should rely on the default implementation
serverTitle :: Typeable (ServerPdu a) => Init a e -> ProcessTitle Source #
Return the ProcessTitle.
Usually you should rely on the default implementation
runEffects :: Init a e -> Eff (Effects a e) x -> Eff e x Source #
Process the effects of the implementation
runEffects :: Effects a e ~ e => Init a e -> Eff (Effects a e) x -> Eff e x Source #
Process the effects of the implementation
onEvent :: Init a e -> Event (ServerPdu a) -> Eff (Effects a e) () Source #
Update the Model based on the Event.
onEvent :: (Show (Init a e), Member Logs (Effects a e)) => Init a e -> Event (ServerPdu a) -> Eff (Effects a e) () Source #
Update the Model based on the Event.
Instances
| TangibleGenServer tag eLoop e => Server (GenServer tag eLoop e) (InterruptableProcess e) Source # | |
Defined in Control.Eff.Concurrent.Protocol.EffectfulServer Associated Types data Init (GenServer tag eLoop e) (InterruptableProcess e) :: Type Source # type ServerPdu (GenServer tag eLoop e) :: Type Source # type Effects (GenServer tag eLoop e) (InterruptableProcess e) :: [Type -> Type] Source # Methods serverTitle :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> ProcessTitle Source # runEffects :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> Eff (Effects (GenServer tag eLoop e) (InterruptableProcess e)) x -> Eff (InterruptableProcess e) x Source # onEvent :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> Event (ServerPdu (GenServer tag eLoop e)) -> Eff (Effects (GenServer tag eLoop e) (InterruptableProcess e)) () 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
| 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 |
start :: forall a q h. (Server a (InterruptableProcess q), Typeable a, Typeable (ServerPdu a), LogsTo h (InterruptableProcess q), SetMember Process (Process q) (Effects a (InterruptableProcess q)), Member Interrupts (Effects a (InterruptableProcess q)), HasCallStack) => Init a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (ServerPdu a)) Source #
Execute the server loop.
Since: 0.24.0
startLink :: forall a q h. (Typeable a, Typeable (ServerPdu a), Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), SetMember Process (Process q) (Effects a (InterruptableProcess q)), Member Interrupts (Effects a (InterruptableProcess q)), HasCallStack) => Init a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (ServerPdu a)) Source #
Execute the server loop.
Since: 0.24.0
protocolServerLoop :: forall q h a. (Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), SetMember Process (Process q) (Effects a (InterruptableProcess q)), Member Interrupts (Effects a (InterruptableProcess q)), Typeable a, Typeable (ServerPdu a)) => Init a (InterruptableProcess q) -> Eff (InterruptableProcess q) () Source #
Execute the server loop.
Since: 0.24.0
GenServer
type TangibleGenServer tag eLoop e = (LogIo e, SetMember Process (Process e) eLoop, Member Interrupts eLoop, Typeable e, Typeable eLoop, Typeable tag) Source #
The constraints for a tangible GenServer instance.
Since: 0.24.1
data GenServer tag eLoop e Source #
Make a Server from a data record instead of type-class instance.
Sometimes it is much more concise to create an inline server-loop. In those cases it might not be practical to go through all this type class boilerplate.
In these cases specifying a server by from a set of callback functions seems much more appropriate.
This is such a helper. The GenServer is a record with to callbacks,
and a Server instance that simply invokes the given callbacks.
Servers that are directly based on LogIo and InterruptableProcess effects.
The name prefix Gen indicates the inspiration from Erlang's gen_server module.
Since: 0.24.1
Instances
newtype GenServerId tag Source #
The name/id of a GenServer for logging purposes.
Since: 0.24.0
Constructors
| MkGenServerId | |
Fields | |
Instances
genServer :: forall tag eLoop e. (HasCallStack, TangibleGenServer tag eLoop e, Server (GenServer tag eLoop e) (InterruptableProcess e)) => (forall x. GenServerId tag -> Eff eLoop x -> Eff (InterruptableProcess e) x) -> (GenServerId tag -> Event tag -> Eff eLoop ()) -> GenServerId tag -> Init (GenServer tag eLoop e) (InterruptableProcess e) Source #
Create a GenServer.
This requires the callback for Events, a initial Model and a GenServerId.
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 Inits from GenServerIds, like a factory
Since: 0.24.0
Re-exports
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
| |