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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.EffectfulServer

Contents

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 EmbedProtocol instances exist, like 2-,3-,4-, or 5-tuple.

Since: 0.24.1

Minimal complete definition

Nothing

Associated Types

data Init a e 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 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 (ServerEffects a e) x -> Eff e x Source #

Process the effects of the implementation

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

Process the effects of the implementation

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

Update the Model based on the Event.

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

Update the Model based on the Event.

Instances
TangibleGenServer tag eLoop e => Server (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

data Init (GenServer tag eLoop e) (Processes e) :: Type Source #

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

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

Methods

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

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

onEvent :: Init (GenServer tag eLoop e) (Processes e) -> Event (ServerPdu (GenServer tag eLoop e)) -> Eff (ServerEffects (GenServer 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 q h. (Server a (Processes q), Typeable a, Typeable (ServerPdu a), LogsTo h (Processes q), SetMember Process (Process q) (ServerEffects a (Processes q)), Member Interrupts (ServerEffects a (Processes q)), HasCallStack) => Init a (Processes q) -> Eff (Processes 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 (Processes q), LogsTo h (Processes q), SetMember Process (Process q) (ServerEffects a (Processes q)), Member Interrupts (ServerEffects a (Processes q)), HasCallStack) => Init a (Processes q) -> Eff (Processes q) (Endpoint (ServerPdu a)) Source #

Execute the server loop.

Since: 0.24.0

protocolServerLoop :: forall q h a. (Server a (Processes q), LogsTo h (Processes q), SetMember Process (Process q) (ServerEffects a (Processes q)), Member Interrupts (ServerEffects a (Processes q)), Typeable a, Typeable (ServerPdu a)) => Init a (Processes q) -> Eff (Processes 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 Processes effects.

The name prefix Gen indicates the inspiration from Erlang's gen_server module.

Since: 0.24.1

Instances
Typeable tag => Show (Init (GenServer tag eLoop e) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

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

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

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

NFData (Init (GenServer tag eLoop e) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

data Init (GenServer tag eLoop e) (Processes e) :: Type Source #

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

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

Methods

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

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

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

type ServerPdu (GenServer tag eLoop e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerPdu (GenServer tag eLoop e) = tag
data Init (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerEffects (GenServer tag eLoop e) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type ServerEffects (GenServer tag eLoop e) (Processes e) = eLoop

newtype GenServerId tag Source #

The name/id of a GenServer for logging purposes.

Since: 0.24.0

Constructors

MkGenServerId 
Instances
Eq (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

(==) :: GenServerId tag -> GenServerId tag -> Bool #

(/=) :: GenServerId tag -> GenServerId tag -> Bool #

Ord (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

compare :: GenServerId tag -> GenServerId tag -> Ordering #

(<) :: GenServerId tag -> GenServerId tag -> Bool #

(<=) :: GenServerId tag -> GenServerId tag -> Bool #

(>) :: GenServerId tag -> GenServerId tag -> Bool #

(>=) :: GenServerId tag -> GenServerId tag -> Bool #

max :: GenServerId tag -> GenServerId tag -> GenServerId tag #

min :: GenServerId tag -> GenServerId tag -> GenServerId tag #

(Typeable k, Typeable tag) => Show (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

showsPrec :: Int -> GenServerId tag -> ShowS #

show :: GenServerId tag -> String #

showList :: [GenServerId tag] -> ShowS #

IsString (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

fromString :: String -> GenServerId tag #

NFData (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

rnf :: GenServerId tag -> () #

genServer :: forall tag eLoop e. (HasCallStack, TangibleGenServer tag eLoop e, Server (GenServer tag eLoop e) (Processes e)) => (forall x. GenServerId tag -> Eff eLoop x -> Eff (Processes e) x) -> (GenServerId tag -> Event tag -> Eff eLoop ()) -> GenServerId tag -> Init (GenServer tag eLoop e) (Processes 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