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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Api.Server

Contents

Description

Functions to implement Api servers.

Synopsis

Api Server

serve :: forall a effScheduler. (Servable a, SetMember Process (Process effScheduler) (ServerEff a), Member Interrupts (ServerEff a), HasCallStack) => SchedulerProxy effScheduler -> a -> Eff (ServerEff a) () Source #

Receive and process incoming requests until the process exits.

spawnServer :: forall a effScheduler eff. (Servable a, ServerEff a ~ InterruptableProcess effScheduler, SetMember Process (Process effScheduler) eff, Member Interrupts eff, HasCallStack) => SchedulerProxy effScheduler -> a -> Eff eff (ServerPids a) Source #

Spawn a new process, that will receive and process incoming requests until the process exits.

spawnServerWithEffects :: forall a effScheduler eff. (Servable a, SetMember Process (Process effScheduler) (ServerEff a), SetMember Process (Process effScheduler) eff, Member Interrupts eff, Member Interrupts (ServerEff a), HasCallStack) => SchedulerProxy effScheduler -> a -> (Eff (ServerEff a) () -> Eff (InterruptableProcess effScheduler) ()) -> Eff eff (ServerPids a) Source #

Spawn a new process, that will receive and process incoming requests until the process exits. Also handle all internal effects.

Api Callbacks

data ApiHandler api eff where Source #

A record of callbacks, handling requests sent to a server Process, all belonging to a specific Api family instance. The values of this type can be serveed or combined via Servable or ServerCallbacks.

Constructors

ApiHandler 

Fields

Instances
Default (ApiHandler api eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Methods

def :: ApiHandler api eff #

Typeable a => Servable (ApiHandler a eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type ServerEff (ApiHandler a eff) :: [Type -> Type] Source #

type ServerPids (ApiHandler a eff) :: Type Source #

type ServerEff (ApiHandler a eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

type ServerEff (ApiHandler a eff) = eff
type ServerPids (ApiHandler a eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

type ServerPids (ApiHandler a eff) = Server a

castCallback :: forall api eff. Lens' (ApiHandler api eff) (Maybe (Api api Asynchronous -> Eff eff ApiServerCmd)) Source #

callCallback :: forall api eff reply. Getter (ApiHandler api eff) (Maybe (Api api (Synchronous reply) -> (reply -> Eff eff ()) -> Eff eff ApiServerCmd)) Source #

terminateCallback :: forall api eff. Lens' (ApiHandler api eff) (Maybe (ExitReason Recoverable -> Eff eff ())) Source #

apiHandler :: (Api api Asynchronous -> Eff e ApiServerCmd) -> (forall r. Api api (Synchronous r) -> (r -> Eff e ()) -> Eff e ApiServerCmd) -> (ExitReason Recoverable -> Eff e ()) -> ApiHandler api e Source #

Create an ApiHandler with a _castCallback, a _callCallback and a _terminateCallback implementation.

apiHandlerForever :: (Api api Asynchronous -> Eff e ()) -> (forall r. Api api (Synchronous r) -> (r -> Eff e ()) -> Eff e ()) -> (ExitReason Recoverable -> Eff e ()) -> ApiHandler api e Source #

Like apiHandler but the server will loop until an error is raised or the process exits. The callback actions won't decide wether to stop the server or not, instead the ApiServerCmd HandleNextRequest is used.

castHandler :: (Api api Asynchronous -> Eff eff ApiServerCmd) -> ApiHandler api eff Source #

Create an ApiHandler with only a _castCallback implementation.

castHandlerForever :: (Api api Asynchronous -> Eff eff ()) -> ApiHandler api eff Source #

Like castHandler but the server will loop until an error is raised or the process exits. See apiHandlerForver.

callHandler :: (forall r. Api api (Synchronous r) -> (r -> Eff e ()) -> Eff e ApiServerCmd) -> ApiHandler api e Source #

Create an ApiHandler with only a _callCallback implementation.

callHandlerForever :: (forall r. Api api (Synchronous r) -> (r -> Eff e ()) -> Eff e ()) -> ApiHandler api e Source #

Like callHandler but the server will loop until an error is raised or the process exits. See apiHandlerForver.

castAndCallHandler :: (Api api Asynchronous -> Eff e ApiServerCmd) -> (forall r. Api api (Synchronous r) -> (r -> Eff e ()) -> Eff e ApiServerCmd) -> ApiHandler api e Source #

Create an ApiHandler with only a _castCallback and _callCallback implementation.

castAndCallHandlerForever :: (Api api Asynchronous -> Eff e ()) -> (forall r. Api api (Synchronous r) -> (r -> Eff e ()) -> Eff e ()) -> ApiHandler api e Source #

Like castAndCallHandler but the server will loop until an error is raised or the process exits. See apiHandlerForver.

data ApiServerCmd 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.

Constructors

HandleNextRequest :: ApiServerCmd

Tell the server to keep the server loop running

StopApiServer :: ExitReason Recoverable -> ApiServerCmd

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 ApiServerCmd Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Generic ApiServerCmd Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type Rep ApiServerCmd :: Type -> Type #

NFData ApiServerCmd Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Methods

rnf :: ApiServerCmd -> () #

type Rep ApiServerCmd Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

type Rep ApiServerCmd = D1 (MetaData "ApiServerCmd" "Control.Eff.Concurrent.Api.Server" "extensible-effects-concurrent-0.13.0-9SIHKBwWVl85L64mvpN8ux" False) (C1 (MetaCons "HandleNextRequest" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StopApiServer" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ExitReason Recoverable))))

unhandledCallError :: forall p x r q. (Typeable p, HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => SchedulerProxy q -> Api p (Synchronous x) -> (x -> Eff r ()) -> Eff r ApiServerCmd Source #

A default handler to use in _callCallback in ApiHandler. It will call raiseError with a nice error message.

unhandledCastError :: forall p r q. (Typeable p, HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => SchedulerProxy q -> Api p Asynchronous -> Eff r ApiServerCmd Source #

A default handler to use in _castCallback in ApiHandler. It will call raiseError with a nice error message.

defaultTermination :: forall q r. (HasCallStack, SetMember Process (Process q) r, Member (Logs LogMessage) r) => SchedulerProxy q -> ExitReason Recoverable -> Eff r () Source #

Either do nothing, if the error message is Nothing, or call exitWithError with the error message.

Callback Composition

class Servable a where Source #

Helper type class to allow composition of ApiHandler.

Associated Types

type ServerEff a :: [Type -> Type] Source #

The effect of the callbacks

type ServerPids a Source #

The is used to let the spawn function return multiple Server ProcessIds in a type safe way, e.g. for a tuple instance of this class (Server a, Server b)

Methods

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

The is used to let the spawn function return multiple Server ProcessIds in a type safe way.

toServerCallback :: (Member Interrupts (ServerEff a), SetMember Process (Process effScheduler) (ServerEff a)) => SchedulerProxy effScheduler -> a -> ServerCallback (ServerEff a) Source #

Convert the value to a ServerCallback

Instances
Servable (ServerCallback eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type ServerEff (ServerCallback eff) :: [Type -> Type] Source #

type ServerPids (ServerCallback eff) :: Type Source #

(ServerEff a ~ ServerEff b, Servable a, Servable b) => Servable (a, b) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type ServerEff (a, b) :: [Type -> Type] Source #

type ServerPids (a, b) :: Type Source #

Methods

toServerPids :: proxy (a, b) -> ProcessId -> ServerPids (a, b) Source #

toServerCallback :: (Member Interrupts (ServerEff (a, b)), SetMember Process (Process effScheduler) (ServerEff (a, b))) => SchedulerProxy effScheduler -> (a, b) -> ServerCallback (ServerEff (a, b)) Source #

Typeable a => Servable (ApiHandler a eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type ServerEff (ApiHandler a eff) :: [Type -> Type] Source #

type ServerPids (ApiHandler a eff) :: Type Source #

data ServerCallback eff Source #

Building block for composition of ApiHandler. A wrapper for ApiHandler. Use this to combine ApiHandler, allowing a process to implement several Api instances. The termination will be evenly propagated. Create this via e.g. Servable instances To serve multiple apis use <> to combine server callbacks, e.g.

@@ let f = apiHandlerServerCallback px $ ApiHandler ... g = apiHandlerServerCallback px $ ApiHandler ... h = f <> g in serve px h @@