extensible-effects-concurrent-0.29.2: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.StatefulServer

Contents

Description

Utilities to implement server-loops with builtin state and TEA-like naming.

Since: 0.24.0

Synopsis

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

update

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 Model a :: Type Source #

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 :: Endpoint (Protocol a) -> StartArgument a q -> Eff q (Model a, Settings a) Source #

Return an initial Model and Settings

setup :: (Default (Model a), Default (Settings a)) => Endpoint (Protocol a) -> StartArgument a q -> Eff q (Model a, Settings a) Source #

Return an initial Model and Settings

update :: Endpoint (Protocol a) -> StartArgument a q -> Event (Protocol a) -> Eff (ModelState a ': (SettingsReader a ': q)) () Source #

Update the Model based on the Event.

Instances
(LogIo q, TangibleSup p, Tangible (ChildId p), Typeable (ServerPdu p), Server p (Processes q), HasProcesses (ServerEffects p (Processes q)) q) => Server (Sup p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

data StartArgument (Sup p) (Processes q) :: Type Source #

type Protocol (Sup p) :: Type Source #

type Model (Sup p) :: Type Source #

type Settings (Sup p) :: Type Source #

(Typeable event, Lifted IO q, Member Logs q) => Server (ObservationQueue event) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

Associated Types

data StartArgument (ObservationQueue event) (Processes q) :: Type Source #

type Protocol (ObservationQueue event) :: Type Source #

type Model (ObservationQueue event) :: Type Source #

type Settings (ObservationQueue event) :: Type Source #

data Stateful a Source #

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 # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.StatefulServer

Associated Types

data Init (Stateful a) q :: Type Source #

type ServerPdu (Stateful a) :: Type Source #

type ServerEffects (Stateful a) q :: [Type -> Type] Source #

data Init (Stateful a) q Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.StatefulServer

data Init (Stateful a) q = Init (StartArgument a q)
type ServerPdu (Stateful a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.StatefulServer

type ServerEffects (Stateful a) q Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.StatefulServer

type ServerEffects (Stateful a) q = ModelState a ': (SettingsReader a ': q)

data family Init a e Source #

The value that defines what is required to initiate a Server loop.

Instances
TangibleCallbacks tag eLoop e => Show (Init (Server tag eLoop) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

showsPrec :: Int -> Init (Server tag eLoop) (Processes e) -> ShowS #

show :: Init (Server tag eLoop) (Processes e) -> String #

showList :: [Init (Server tag eLoop) (Processes e)] -> ShowS #

TangibleCallbacks tag eLoop e => NFData (Init (Server tag eLoop) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

rnf :: Init (Server tag eLoop) (Processes e) -> () #

data Init (Stateful a) q Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.StatefulServer

data Init (Stateful a) q = Init (StartArgument a q)
data Init (Server tag eLoop) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

data Init (Server tag eLoop) (Processes e) = MkServer {}

start :: forall a r q h. (HasCallStack, Typeable a, LogsTo h (Processes q), Server (Stateful a) (Processes q), Server a (Processes q), HasProcesses r q) => StartArgument a (Processes q) -> Eff r (Endpoint (Protocol a)) Source #

Execute the server loop.

Since: 0.24.0

startLink :: forall a r q h. (HasCallStack, Typeable a, LogsTo h (Processes q), Server (Stateful a) (Processes q), Server a (Processes q), HasProcesses r q) => StartArgument a (Processes q) -> Eff r (Endpoint (Protocol a)) Source #

Execute the server loop.

Since: 0.24.0

type ModelState a = State (Model a) Source #

The Effect type of mutable Model in a Server instance.

Since: 0.24.0

modifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e () Source #

Modify the Model of a Server.

Since: 0.24.0

getAndModifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a) Source #

Modify the Model of a Server and return the old value.

Since: 0.24.0

modifyAndGetModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a) Source #

Modify the Model of a Server and return the new value.

Since: 0.24.0

getModel :: forall a e. Member (ModelState a) e => Eff e (Model a) Source #

Return the Model of a Server.

Since: 0.24.0

putModel :: forall a e. Member (ModelState a) e => Model a -> Eff e () Source #

Overwrite the Model of a Server.

Since: 0.24.0

getAndPutModel :: forall a e. Member (ModelState a) e => Model a -> Eff e (Model a) Source #

Overwrite the Model of a Server, return the old value.

Since: 0.24.0

useModel :: forall a b e. Member (ModelState a) e => Getting b (Model a) b -> Eff e b Source #

Return a element selected by a Lens of the Model of a Server.

Since: 0.24.0

zoomModel :: forall a b c e. Member (ModelState a) e => Lens' (Model a) b -> Eff (State b ': e) c -> Eff e c Source #

Run an action that modifies portions of the Model of a Server defined by the given Lens.

Since: 0.24.0

type SettingsReader a = Reader (Settings a) Source #

The Effect type of readonly Settings in a Server instance.

Since: 0.24.0

askSettings :: forall a e. Member (SettingsReader a) e => Eff e (Settings a) Source #

Return the read-only Settings of a Server

Since: 0.24.0

viewSettings :: forall a b e. Member (SettingsReader a) e => Getting b (Settings a) b -> Eff e b Source #

Return the read-only Settings of a Server as viewed through a Lens

Since: 0.24.0

Re-exports

data Event a where Source #

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 Synchronous message was received. If an implementation wants to delegate nested Pdus, it can use toEmbeddedReplyTarget to convert a ReplyTarget safely to the embedded protocol.

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 
Instances
Show (Event a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

NFData a => NFData (Event a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

rnf :: Event a -> () #

type ToPretty (Event a :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ToPretty (Event a :: Type) = ToPretty a <+> PutStr "event"