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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.EffectfulServer

Description

Utilities to implement effectful server-loops.

Since: 0.24.0

Synopsis

Documentation

class Server (a :: Type) (e :: [Type -> Type]) where Source #

A type class for effectful 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 Embeds instances exist, like 2-,3-,4-, or 5-tuple.

Since: 0.24.1

Minimal complete definition

Nothing

Associated Types

data Init a Source #

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 ServerEffects a e :: [Type -> Type] Source #

Effects of the implementation

Since: 0.24.1

Methods

serverTitle :: Init a -> ProcessTitle Source #

Return the ProcessTitle.

Usually you should rely on the default implementation

serverTitle :: Typeable a => Init a -> ProcessTitle Source #

Return the ProcessTitle.

Usually you should rely on the default implementation

runEffects :: Endpoint (ServerPdu a) -> Init a -> Eff (ServerEffects a e) x -> Eff e x Source #

Process the effects of the implementation

runEffects :: ServerEffects a e ~ e => Endpoint (ServerPdu a) -> Init a -> Eff (ServerEffects a e) x -> Eff e x Source #

Process the effects of the implementation

onEvent :: Endpoint (ServerPdu a) -> Init a -> Event (ServerPdu a) -> Eff (ServerEffects a e) () Source #

Update the Model based on the Event.

onEvent :: (Show (Init a), Member Logs (ServerEffects a e)) => Endpoint (ServerPdu a) -> Init a -> Event (ServerPdu a) -> Eff (ServerEffects a e) () Source #

Update the Model based on the Event.

Instances
Server a q => Server (Stateful a) q Source # 
Instance details

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 #

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

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Associated Types

data Init (Server tag eLoop e) :: Type Source #

type ServerPdu (Server tag eLoop e) :: Type Source #

type ServerEffects (Server tag eLoop e) (Processes e) :: [Type -> Type] Source #

Methods

serverTitle :: Init (Server tag eLoop e) -> ProcessTitle Source #

runEffects :: Endpoint (ServerPdu (Server tag eLoop e)) -> Init (Server tag eLoop e) -> Eff (ServerEffects (Server tag eLoop e) (Processes e)) x -> Eff (Processes e) x Source #

onEvent :: Endpoint (ServerPdu (Server tag eLoop e)) -> Init (Server tag eLoop e) -> Event (ServerPdu (Server tag eLoop e)) -> Eff (ServerEffects (Server tag eLoop e) (Processes e)) () Source #

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"

start :: forall a r q. (Server a (Processes q), Typeable a, Typeable (ServerPdu a), FilteredLogging (Processes q), HasProcesses (ServerEffects a (Processes q)) q, HasProcesses r q, HasCallStack) => Init a -> Eff r (Endpoint (ServerPdu a)) Source #

Execute the server loop.

Since: 0.24.0

startLink :: forall a r q. (Typeable a, Typeable (ServerPdu a), Server a (Processes q), FilteredLogging (Processes q), HasProcesses (ServerEffects a (Processes q)) q, HasProcesses r q, HasCallStack) => Init a -> Eff r (Endpoint (ServerPdu a)) Source #

Execute the server loop.

Since: 0.24.0

protocolServerLoop :: forall q a. (Server a (Processes q), FilteredLogging (Processes q), HasProcesses (ServerEffects a (Processes q)) q, Typeable a, Typeable (ServerPdu a)) => Init a -> Eff (Processes q) () Source #

Execute the server loop.

Since: 0.24.0