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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.CallbackServer

Description

Build a Control.Eff.Concurrent.EffectfulServer from callbacks.

This module contains in instance of Server that delegates to callback functions.

Since: 0.27.0

Synopsis

Documentation

start :: forall tag eLoop q h. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop) (Processes q), LogsTo h (Processes q)) => (forall x. Endpoint tag -> Eff eLoop x -> Eff (Processes q) x) -> (Endpoint tag -> Event tag -> Eff eLoop ()) -> ServerId tag -> Eff (Processes q) (Endpoint tag) Source #

Execute the server loop.

Since: 0.27.0

startLink :: forall tag eLoop q h. (HasCallStack, TangibleCallbacks tag eLoop q, Server (Server tag eLoop) (Processes q), LogsTo h (Processes q)) => (forall x. Endpoint tag -> Eff eLoop x -> Eff (Processes q) x) -> (Endpoint tag -> Event tag -> Eff eLoop ()) -> ServerId tag -> Eff (Processes q) (Endpoint tag) Source #

Execute the server loop.

Since: 0.27.0

data Server tag eLoop Source #

Phantom type to indicate a callback based Server instance.

Since: 0.27.0

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) -> () #

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

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Associated Types

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

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

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

Methods

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

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

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

type ServerPdu (Server tag eLoop) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

type ServerPdu (Server tag eLoop) = tag
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 {}
type ServerEffects (Server tag eLoop) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

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

newtype ServerId (tag :: Type) Source #

The name/id of a Server for logging purposes.

Since: 0.24.0

Constructors

MkServerId 

Fields

Instances
Eq (ServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

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

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

Ord (ServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

compare :: ServerId tag -> ServerId tag -> Ordering #

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

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

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

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

max :: ServerId tag -> ServerId tag -> ServerId tag #

min :: ServerId tag -> ServerId tag -> ServerId tag #

Typeable tag => Show (ServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

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

show :: ServerId tag -> String #

showList :: [ServerId tag] -> ShowS #

IsString (ServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

fromString :: String -> ServerId tag #

NFData (ServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Methods

rnf :: ServerId tag -> () #

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"

type TangibleCallbacks 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 Server instance.

Since: 0.27.0