| 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
- type Protocol a :: Type
- data Model a :: Type
- type Settings a :: Type
- title :: StartArgument a -> ProcessTitle
- setup :: Endpoint (Protocol a) -> StartArgument a -> Eff q (Model a, Settings a)
- update :: Endpoint (Protocol a) -> StartArgument a -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': q)) ()
- data Stateful a
- data family Init a
- startLink :: forall a r q. (HasCallStack, Typeable a, FilteredLogging (Processes q), Server (Stateful a) (Processes q), Server a (Processes q), HasProcesses r q) => StartArgument a -> Eff r (Endpoint (Protocol a))
- start :: forall a r q. (HasCallStack, Typeable a, Server (Stateful a) (Processes q), Server a (Processes q), FilteredLogging (Processes q), HasProcesses r q) => StartArgument a -> Eff r (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
- preuseModel :: forall a b e. Member (ModelState a) e => Getting (First b) (Model a) b -> Eff e (Maybe b)
- zoomModel :: forall a b c e. Member (ModelState a) e => Lens' (Model a) b -> Eff (State b ': e) c -> Eff e c
- logModel :: forall m e q. (Show (Model m), Member Logs e, HasProcesses e q, Member (ModelState m) e) => Text -> Eff e ()
- 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
- mapEffects :: forall inner outer a e. (Settings outer -> Settings inner) -> Lens' (Model outer) (Model inner) -> Eff (ModelState inner ': (SettingsReader inner ': e)) a -> Eff (ModelState outer ': (SettingsReader outer ': e)) a
- coerceEffects :: forall inner outer a e. (Coercible (Model inner) (Model outer), Coercible (Model outer) (Model inner), Coercible (Settings outer) (Settings inner)) => Eff (ModelState inner ': (SettingsReader inner ': e)) a -> Eff (ModelState outer ': (SettingsReader outer ': e)) a
- data Event a where
- OnCall :: forall a r. (Tangible r, TangiblePdu a (Synchronous r)) => ReplyTarget 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
Documentation
class Typeable (Protocol a) => Server (a :: Type) q where Source #
A type class for server loops.
This class serves as interface for other mechanisms, for example process supervision
The methods of this class handle Events and Requests for Pdu instances.
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 Embeds
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 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
title :: StartArgument a -> ProcessTitle Source #
Return a new ProcessTitle for the stateful process,
while it is running.
Since: 0.30.0
title :: Typeable a => StartArgument a -> ProcessTitle Source #
Return a new ProcessTitle for the stateful process,
while it is running.
Since: 0.30.0
setup :: Endpoint (Protocol a) -> StartArgument a -> Eff q (Model a, Settings a) Source #
setup :: (Default (Model a), Default (Settings a)) => Endpoint (Protocol a) -> StartArgument a -> Eff q (Model a, Settings a) Source #
update :: Endpoint (Protocol a) -> StartArgument a -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': q)) () Source #
Update the Model based on the Event.
Instances
This type is used to build stateful EffectfulServer instances.
It is a variant of EffectfulServer, that comes pre-installed
with State and Reader effects.
Since: 0.24.0
Instances
| Server a q => Server (Stateful a) q Source # | |
Defined in Control.Eff.Concurrent.Protocol.StatefulServer Associated Types data Init (Stateful a) :: Type Source # type ServerPdu (Stateful a) :: Type Source # type ServerEffects (Stateful a) q :: [Type -> Type] Source # Methods serverTitle :: Init (Stateful a) -> ProcessTitle Source # runEffects :: Endpoint (ServerPdu (Stateful a)) -> Init (Stateful a) -> Eff (ServerEffects (Stateful a) q) x -> Eff q x Source # onEvent :: Endpoint (ServerPdu (Stateful a)) -> Init (Stateful a) -> Event (ServerPdu (Stateful a)) -> Eff (ServerEffects (Stateful a) q) () Source # | |
| data Init (Stateful a) Source # | |
| type ServerPdu (Stateful a) Source # | |
| type ChildId (Stateful p) Source # | |
Defined in Control.Eff.Concurrent.Protocol.Broker | |
| type ServerEffects (Stateful a) q Source # | |
The value that defines what is required to initiate a Server
loop.
Instances
| TangibleCallbacks tag eLoop e => Show (Init (Server tag eLoop e)) Source # | |
| TangibleCallbacks tag eLoop e => NFData (Init (Server tag eLoop e)) Source # | |
| data Init (Stateful a) Source # | |
| data Init (Server tag eLoop e) Source # | |
Defined in Control.Eff.Concurrent.Protocol.CallbackServer data Init (Server tag eLoop e) = MkServer {
| |
startLink :: forall a r q. (HasCallStack, Typeable a, FilteredLogging (Processes q), Server (Stateful a) (Processes q), Server a (Processes q), HasProcesses r q) => StartArgument a -> Eff r (Endpoint (Protocol a)) Source #
Execute the server loop.
Since: 0.24.0
start :: forall a r q. (HasCallStack, Typeable a, Server (Stateful a) (Processes q), Server a (Processes q), FilteredLogging (Processes q), HasProcesses r q) => StartArgument a -> Eff r (Endpoint (Protocol a)) Source #
Execute the server loop. Please use startLink if you can.
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 #
preuseModel :: forall a b e. Member (ModelState a) e => Getting (First b) (Model a) b -> Eff e (Maybe b) Source #
zoomModel :: forall a b c e. Member (ModelState a) e => Lens' (Model a) b -> Eff (State b ': e) c -> Eff e c Source #
logModel :: forall m e q. (Show (Model m), Member Logs e, HasProcesses e q, Member (ModelState m) e) => Text -> Eff e () 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 #
Arguments
| :: (Settings outer -> Settings inner) | A function to get the inner settings out of the outer settings |
| -> Lens' (Model outer) (Model inner) | A |
| -> Eff (ModelState inner ': (SettingsReader inner ': e)) a | |
| -> Eff (ModelState outer ': (SettingsReader outer ': e)) a |
Map ModelState and SettingsReader effects.
Use this to embed update from another Server instance.
Since: 0.30.0
coerceEffects :: forall inner outer a e. (Coercible (Model inner) (Model outer), Coercible (Model outer) (Model inner), Coercible (Settings outer) (Settings inner)) => Eff (ModelState inner ': (SettingsReader inner ': e)) a -> Eff (ModelState outer ': (SettingsReader outer ': e)) a Source #
Coerce Coercible ModelState and SettingsReader effects.
Use this to embed update from a similar Server instance.
Since: 0.30.0
Re-exports
This event sum-type is used to communicate incoming messages and other events to the
instances of Server.
Since: 0.24.0
Constructors
| OnCall :: forall a r. (Tangible r, TangiblePdu a (Synchronous r)) => ReplyTarget 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 |