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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Protocol.Server

Contents

Description

A better, more safe implementation of the Erlang/OTP gen_server behaviour.

Since: 0.24.0

Synopsis

Documentation

class Typeable (Protocol a) => Server (a :: Type) e where Source #

A type class for Pdu values that have an implementation which handles the corresponding protocol.

Since: 0.24.0

Minimal complete definition

update

Associated Types

data StartArgument a e Source #

The value that defines what is required to initiate a Server loop.

type Protocol 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 Model a :: Type Source #

Type of the model data, given to every invocation of update via the ModelState effect. The model of a server loop is changed through incoming Events. It is initially calculated by setup.

type Settings a :: Type Source #

Type of read-only state.

Instances
(TangibleObserver o, TangiblePdu (Observer o) Asynchronous, Lifted IO q, Member Logs q) => Server (ObservationQueue o) (InterruptableProcess q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer.Queue

(Typeable (GenServerProtocol tag), LogIo e) => Server (GenServer tag e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Associated Types

data StartArgument (GenServer tag e) (InterruptableProcess e) :: Type Source #

type Protocol (GenServer tag e) :: Type Source #

type Model (GenServer tag e) :: Type Source #

type Settings (GenServer tag e) :: Type Source #

(Lifted IO q, LogsTo IO q, TangibleSup p, Tangible (ChildId p), Server p (InterruptableProcess q)) => Server (Sup p) (InterruptableProcess q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Associated Types

data StartArgument (Sup p) (InterruptableProcess q) :: Type Source #

type Protocol (Sup p) :: Type Source #

type Model (Sup p) :: Type Source #

type Settings (Sup p) :: Type Source #

type ToServerEffects a e = ModelState a ': (SettingsReader a ': e) Source #

Cons (i.e. prepend) ModelState and SettingsReader to an effect list.

Since: 0.24.0

type ModelState a = State (Model a) Source #

The Effect type of mutable Model in a Server instance.

Since: 0.24.0

modifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e () Source #

Modify the Model of a Server.

Since: 0.24.0

getAndModifyModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a) Source #

Modify the Model of a Server and return the old value.

Since: 0.24.0

modifyAndGetModel :: forall a e. Member (ModelState a) e => (Model a -> Model a) -> Eff e (Model a) Source #

Modify the Model of a Server and return the new value.

Since: 0.24.0

getModel :: forall a e. Member (ModelState a) e => Eff e (Model a) Source #

Return the Model of a Server.

Since: 0.24.0

putModel :: forall a e. Member (ModelState a) e => Model a -> Eff e () Source #

Overwrite the Model of a Server.

Since: 0.24.0

getAndPutModel :: forall a e. Member (ModelState a) e => Model a -> Eff e (Model a) Source #

Overwrite the Model of a Server, return the old value.

Since: 0.24.0

useModel :: forall a b e. Member (ModelState a) e => Getting b (Model a) b -> Eff e b Source #

Return a element selected by a Lens of the Model of a Server.

Since: 0.24.0

zoomModel :: forall a b c e. Member (ModelState a) e => Lens' (Model a) b -> Eff (State b ': e) c -> Eff e c Source #

Run an action that modifies portions of the Model of a Server defined by the given Lens.

Since: 0.24.0

type SettingsReader a = Reader (Settings a) Source #

The Effect type of readonly Settings in a Server instance.

Since: 0.24.0

askSettings :: forall a e. Member (SettingsReader a) e => Eff e (Settings a) Source #

Return the read-only Settings of a Server

Since: 0.24.0

viewSettings :: forall a b e. Member (SettingsReader a) e => Getting b (Settings a) b -> Eff e b Source #

Return the read-only Settings of a Server as viewed through a Lens

Since: 0.24.0

data Event a Source #

Internal protocol to communicate incoming messages and other events to the instances of Server.

Note that this is required to receive any kind of messages in protocolServerLoop.

Since: 0.24.0

Instances
Show (Event a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Methods

showsPrec :: Int -> Event a -> ShowS #

show :: Event a -> String #

showList :: [Event a] -> ShowS #

Generic (Event a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Associated Types

type Rep (Event a) :: Type -> Type #

Methods

from :: Event a -> Rep (Event a) x #

to :: Rep (Event a) x -> Event a #

NFData a => NFData (Event a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Methods

rnf :: Event a -> () #

type Rep (Event a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

type ToPretty (Event a :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

type ToPretty (Event a :: Type) = ToPretty a <+> PutStr "event"

start :: forall a q h. (Server a (InterruptableProcess q), Typeable a, LogsTo h (InterruptableProcess q), HasCallStack) => StartArgument a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (Protocol a)) Source #

Execute the server loop.

Since: 0.24.0

startLink :: forall a q h. (Typeable a, Server a (InterruptableProcess q), LogsTo h (InterruptableProcess q), HasCallStack) => StartArgument a (InterruptableProcess q) -> Eff (InterruptableProcess q) (Endpoint (Protocol a)) Source #

Execute the server loop.

Since: 0.24.0

protocolServerLoop :: forall q e h a. (Server a e, SetMember Process (Process q) e, Member Interrupts e, LogsTo h e, Typeable a) => StartArgument a e -> Eff e () Source #

Execute the server loop.

Since: 0.24.0

data GenServer tag e where Source #

A helper for Servers that are directly based on logging and IO: GenIO

A record that contains callbacks to provide a Server instance for the tag parameter, .

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

Since: 0.24.0

Constructors

MkGenServer 

Fields

Instances
Typeable tag => Show (StartArgument (GenServer tag e) (InterruptableProcess e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

NFData (StartArgument (GenServer tag e) (InterruptableProcess e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Methods

rnf :: StartArgument (GenServer tag e) (InterruptableProcess e) -> () #

(Typeable (GenServerProtocol tag), LogIo e) => Server (GenServer tag e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Associated Types

data StartArgument (GenServer tag e) (InterruptableProcess e) :: Type Source #

type Protocol (GenServer tag e) :: Type Source #

type Model (GenServer tag e) :: Type Source #

type Settings (GenServer tag e) :: Type Source #

type Protocol (GenServer tag e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

type Model (GenServer tag e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

type Model (GenServer tag e) = GenServerModel tag
type Settings (GenServer tag e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

data StartArgument (GenServer tag e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

type ToGenServerEffects tag e = ToServerEffects (GenServer tag e) (InterruptableProcess e) Source #

Prepend the ModelState for GenServerModel and SettingsReader for GenServerSettings of a GenServer Server to an effect list.

Since: 0.24.0

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.Server

Methods

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

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

Ord (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

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 #

Show (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

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.Server

Methods

fromString :: String -> GenServerId tag #

NFData (GenServerId tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

Methods

rnf :: GenServerId tag -> () #

type family GenServerProtocol tag Source #

The Protocol un-wrapper type function.

Since: 0.24.0

type family GenServerModel tag Source #

Type of state for GenServer based Servers

Since: 0.24.0

Instances
type GenServerModel (Stateless tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

type GenServerModel (Stateless tag) = ()

type family GenServerSettings tag Source #

Type of the environment for GenServer based Servers

Since: 0.24.0

Instances
type GenServerSettings (Stateless tag) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Server

genServer :: forall tag e. (Typeable tag, HasCallStack, LogIo e, Server (GenServer tag e) (InterruptableProcess e)) => (GenServerId tag -> Eff (InterruptableProcess e) (GenServerModel tag, GenServerSettings tag)) -> (GenServerId tag -> Event (GenServerProtocol tag) -> Eff (ToGenServerEffects tag e) ()) -> GenServerId tag -> StartArgument (GenServer tag e) (InterruptableProcess e) Source #

Create a GenServer.

This requires the callback for Events, a initial Model and a GenServerId.

There must be a GenServerModel instance. There must be a GenServerSettings instance. 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 StartArguments from GenServerIds, like a factory

Since: 0.24.0

data Stateless tag Source #

The type-level tag indicating a stateless Server instance.

There are GenServerModel, GenServerSettings and GenServerProtocol as well as ToPretty instances for this type.

See also ToStatelessEffects.

Since: 0.24.0

type ToStatelessEffects e = State () ': (Reader () ': e) Source #

Prepend the ModelState and SettingsReader of a Stateless Server to an effect list. The Model and Settings of a Stateless Server are just () unit.

Since: 0.24.0

statelessGenServer :: forall tag e. (Typeable tag, HasCallStack, LogIo e, Typeable tag, Server (GenServer (Stateless tag) e) (InterruptableProcess e)) => (GenServerId tag -> Event (GenServerProtocol tag) -> Eff (ToStatelessEffects (InterruptableProcess e)) ()) -> GenServerId tag -> StartArgument (GenServer (Stateless tag) e) (InterruptableProcess e) Source #

Create a Stateless GenServer.

This requires only the callback for Events and a GenServerId.

This is Haskell, so if this functions is partially applied to some Event callback, you get a function back, that generates StartArguments from GenServerIds, like a factory

Since: 0.24.0

Re-exports

data Request protocol where Source #

A wrapper sum type for calls and casts for the Pdus of a protocol

Since: 0.15.0

Constructors

Call :: forall protocol reply. (Tangible reply, TangiblePdu protocol (Synchronous reply)) => RequestOrigin protocol reply -> Pdu protocol (Synchronous reply) -> Request protocol 
Cast :: forall protocol. TangiblePdu protocol Asynchronous => Pdu protocol Asynchronous -> Request protocol 
Instances
Show (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

showsPrec :: Int -> Request protocol -> ShowS #

show :: Request protocol -> String #

showList :: [Request protocol] -> ShowS #

NFData (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: Request protocol -> () #

sendReply :: (SetMember Process (Process q) eff, Member Interrupts eff, Tangible reply, Typeable protocol) => RequestOrigin protocol reply -> reply -> Eff eff () Source #

Send a Reply to a Call.

The reply will be deeply evaluated to rnf.

Since: 0.15.0

data RequestOrigin (proto :: Type) reply Source #

Wraps the source ProcessId and a unique identifier for a Call.

Since: 0.15.0

Instances
Eq (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

(==) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(/=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

Ord (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

compare :: RequestOrigin proto reply -> RequestOrigin proto reply -> Ordering #

(<) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(<=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

(>=) :: RequestOrigin proto reply -> RequestOrigin proto reply -> Bool #

max :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

min :: RequestOrigin proto reply -> RequestOrigin proto reply -> RequestOrigin proto reply #

Show (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Generic (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Associated Types

type Rep (RequestOrigin proto reply) :: Type -> Type #

Methods

from :: RequestOrigin proto reply -> Rep (RequestOrigin proto reply) x #

to :: Rep (RequestOrigin proto reply) x -> RequestOrigin proto reply #

NFData (RequestOrigin p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

Methods

rnf :: RequestOrigin p r -> () #

type Rep (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Request

type Rep (RequestOrigin proto reply) = D1 (MetaData "RequestOrigin" "Control.Eff.Concurrent.Protocol.Request" "extensible-effects-concurrent-0.24.0-BtHlQYoXrWzBKtecAAHdT4" False) (C1 (MetaCons "RequestOrigin" PrefixI True) (S1 (MetaSel (Just "_requestOriginPid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId) :*: S1 (MetaSel (Just "_requestOriginCallRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))