extensible-effects-concurrent-0.24.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 type class serves as interface for other abstractions, for example process supervision

The methods of this class handle Events Requests for Pdu instance.

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

Return an initial Model and Settings

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

Return an initial Model and Settings

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

Update the Model based on the Event.

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 #

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 #

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 Synchronous message was received. If an implementation wants to delegate nested Pdus, it can contramap the reply Serializer such that the Reply received by the caller has the correct type.

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"

data RequestOrigin (proto :: Type) reply Source #

Wraps the source ProcessId and a unique identifier for a Call.

Since: 0.15.0

Instances
Eq (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

(==) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(/=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

Ord (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

compare :: RequestOrigin proto reply -> RequestOrigin proto reply -> Ordering #

(<) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(<=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

max :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

min :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

Show (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Generic (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Associated Types

type Rep (RequestOrigin proto reply) :: Type -> Type #

Methods

from :: RequestOrigin proto reply -> Rep (RequestOrigin proto reply) x #

to :: Rep (RequestOrigin proto reply) x -> RequestOrigin proto reply #

NFData (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: RequestOrigin p r -> () #

type Rep (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

type Rep (RequestOrigin proto reply) = D1 (MetaData "RequestOrigin" "Control.Eff.Concurrent.Protocol.Request" "extensible-effects-concurrent-0.24.2-4i89KX4lrqK4F8mqMzm4qM" False) (C1 (MetaCons "RequestOrigin" PrefixI True) (S1 (MetaSel (Just "_requestOriginPid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId) :*: S1 (MetaSel (Just "_requestOriginCallRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))

data Reply protocol reply where Source #

The wrapper around replies to Calls.

Since: 0.15.0

Constructors

Reply 

Fields

Instances
Show r => Show (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> Reply p r -> ShowS #

show :: Reply p r -> String #

showList :: [Reply p r] -> ShowS #

NFData (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: Reply p r -> () #

sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => Serializer (Reply protocol reply) -> RequestOrigin protocol reply -> reply -> Eff eff () Source #

Send a Reply to a Call.

The reply will be deeply evaluated to rnf.

To send replies for EmbedProtocol instances use embedReplySerializer.

Since: 0.15.0