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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Api.Server2

Contents

Description

Experimental new Api server handler.

Since: 0.13.2

Synopsis

Starting Api Servers

spawnApiServer :: forall api eff. (ToServerPids api, HasCallStack) => MessageCallback api (InterruptableProcess eff) -> InterruptCallback (ConsProcess eff) -> Eff (InterruptableProcess eff) (ServerPids api) Source #

Server an Api in a newly spawned process.

Since: 0.13.2

spawnApiServerStateful :: forall api eff state. HasCallStack => Eff (InterruptableProcess eff) state -> MessageCallback api (State state ': InterruptableProcess eff) -> InterruptCallback (State state ': ConsProcess eff) -> Eff (InterruptableProcess eff) (Server api) Source #

Server an Api in a newly spawned process; the callbacks have access to some state initialed by the function in the first parameter.

Since: 0.13.2

spawnApiServerEffectful :: forall api eff serverEff. (HasCallStack, Member Interrupts serverEff, SetMember Process (Process eff) serverEff) => (forall b. Eff serverEff b -> Eff (InterruptableProcess eff) b) -> MessageCallback api serverEff -> InterruptCallback serverEff -> Eff (InterruptableProcess eff) (Server api) Source #

Server an Api in a newly spawned process; The caller provides an effect handler for arbitrary effects used by the server callbacks.

Since: 0.13.2

Api Server Callbacks

data CallbackResult where Source #

A command to the server loop started e.g. by server or spawnServerWithEffects. Typically returned by an ApiHandler member to indicate if the server should continue or stop.

Since: 0.13.2

Constructors

HandleNext :: CallbackResult

Tell the server to keep the server loop running

StopServer :: InterruptReason -> CallbackResult

Tell the server to exit, this will make serve stop handling requests without exitting the process. _terminateCallback will be invoked with the given optional reason.

Instances
Show CallbackResult Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Generic CallbackResult Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Associated Types

type Rep CallbackResult :: Type -> Type #

NFData CallbackResult Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Methods

rnf :: CallbackResult -> () #

type Rep CallbackResult Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

type Rep CallbackResult = D1 (MetaData "CallbackResult" "Control.Eff.Concurrent.Api.Server2" "extensible-effects-concurrent-0.13.2-3xwsT8bAE9w99CMD3teFRT" False) (C1 (MetaCons "HandleNext" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StopServer" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InterruptReason)))

data MessageCallback api eff where Source #

An existential wrapper around a MessageSelector and a function that handles the selected message. The api type parameter is a phantom type.

The return value if the handler function is a CallbackResult.

Since: 0.13.2

Constructors

MessageCallback :: MessageSelector a -> (a -> Eff eff CallbackResult) -> MessageCallback api eff 
Instances
Semigroup (MessageCallback api eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Methods

(<>) :: MessageCallback api eff -> MessageCallback api eff -> MessageCallback api eff #

sconcat :: NonEmpty (MessageCallback api eff) -> MessageCallback api eff #

stimes :: Integral b => b -> MessageCallback api eff -> MessageCallback api eff #

Monoid (MessageCallback api eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Methods

mempty :: MessageCallback api eff #

mappend :: MessageCallback api eff -> MessageCallback api eff -> MessageCallback api eff #

mconcat :: [MessageCallback api eff] -> MessageCallback api eff #

Default (MessageCallback api eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Methods

def :: MessageCallback api eff #

Callback Smart Contructors

Calls and Casts (for Apis)

handleCasts :: forall api eff. (HasCallStack, NFData (Api api Asynchronous), Typeable (Api api Asynchronous)) => (Api api Asynchronous -> Eff eff CallbackResult) -> MessageCallback api eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

handleCalls :: forall api eff reply. (HasCallStack, NFData (Api api (Synchronous reply)), Typeable (Api api (Synchronous reply))) => (Api api (Synchronous reply) -> Eff eff CallbackResult) -> MessageCallback api eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

handleCastsAndCalls :: forall api eff reply. (HasCallStack, NFData (Api api (Synchronous reply)), Typeable (Api api (Synchronous reply)), NFData (Api api Asynchronous), Typeable (Api api Asynchronous)) => (Api api Asynchronous -> Eff eff CallbackResult) -> (Api api (Synchronous reply) -> Eff eff CallbackResult) -> MessageCallback api eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

Generic Message Handler

handleMessages :: forall eff a. (HasCallStack, NFData a, Typeable a) => (a -> Eff eff CallbackResult) -> MessageCallback '[] eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

handleSelectedMessages :: forall eff a. HasCallStack => MessageSelector a -> (a -> Eff eff CallbackResult) -> MessageCallback '[] eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

handleAnyMessages :: forall eff. HasCallStack => (Dynamic -> Eff eff CallbackResult) -> MessageCallback '[] eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

handleProcessDowns :: forall eff. HasCallStack => (MonitorReference -> Eff eff CallbackResult) -> MessageCallback '[] eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

Fallback Handler

dropUnhandledMessages :: forall eff. HasCallStack => MessageCallback '[] eff Source #

A fallbackHandler that drops the left-over messages.

Since: 0.13.2

exitOnUnhandled :: forall eff. HasCallStack => MessageCallback '[] eff Source #

A fallbackHandler that terminates if there are unhandled messages.

Since: 0.13.2

logUnhandledMessages :: forall eff. (Member (Logs LogMessage) eff, HasCallStack) => MessageCallback '[] eff Source #

A fallbackHandler that drops the left-over messages.

Since: 0.13.2

Api Composition

(^:) :: forall (api1 :: Type) (apis2 :: [Type]) eff. HasCallStack => MessageCallback api1 eff -> MessageCallback apis2 eff -> MessageCallback (api1 ': apis2) eff infixr 5 Source #

Compose two Apis to a type-leve pair of them.

handleCalls api1calls ^: handleCalls api2calls ^:

Since: 0.13.2

fallbackHandler :: forall api eff. HasCallStack => MessageCallback api eff -> MessageCallback '[] eff Source #

Make a fallback handler, i.e. a handler to which no other can be composed to from the right.

Since: 0.13.2

class ToServerPids (t :: k) where Source #

Helper type class for the return values of spawnApiServer et al.

Since: 0.13.2

Associated Types

type ServerPids t Source #

Methods

toServerPids :: proxy t -> ProcessId -> ServerPids t Source #

Instances
ToServerPids api1 => ToServerPids (api1 :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Associated Types

type ServerPids api1 :: Type Source #

Methods

toServerPids :: proxy api1 -> ProcessId -> ServerPids api1 Source #

ToServerPids ([] :: [k]) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Associated Types

type ServerPids [] :: Type Source #

Methods

toServerPids :: proxy [] -> ProcessId -> ServerPids [] Source #

(ToServerPids api1, ToServerPids api2) => ToServerPids (api1 ': api2 :: [Type]) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Associated Types

type ServerPids (api1 ': api2) :: Type Source #

Methods

toServerPids :: proxy (api1 ': api2) -> ProcessId -> ServerPids (api1 ': api2) Source #

Interrupt handler

data InterruptCallback eff where Source #

Just a wrapper around a function that will be applied to the result of a MessageCallbacks StopServer clause, or an InterruptReason caught during the execution of receive or a MessageCallback

Since: 0.13.2

Instances
Default (InterruptCallback eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server2

Methods

def :: InterruptCallback eff #

stopServerOnInterrupt :: forall eff. HasCallStack => InterruptCallback eff Source #

A smart constructor for InterruptCallbacks

Since: 0.13.2