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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent

Contents

Description

Erlang style processes with message passing concurrency based on (more) extensible-effects.

This module re-exports most of the library.

There are several scheduler implementations to choose from.

This module re-exports Control.Eff.Concurrent.Process.ForkIOScheduler.

To use another scheduler implementation, don't import this module, but instead import one of:

Synopsis

Concurrent Processes with Message Passing Concurrency

newtype ProcessId Source #

Each process is identified by a single process id, that stays constant throughout the life cycle of a process. Also, message sending relies on these values to address messages to processes.

Constructors

ProcessId 

Fields

Instances
Bounded ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Enum ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Eq ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Integral ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Num ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Read ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Real ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessId Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessId -> () #

data ProcessDown Source #

A monitored process exited. This message is sent to a process by the scheduler, when a process that was monitored died.

Since: 0.12.0

Instances
Eq ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessDown :: Type -> Type #

NFData ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessDown -> () #

type Rep ProcessDown Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessDown = D1 (MetaData "ProcessDown" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "ProcessDown" PrefixI True) (S1 (MetaSel (Just "downReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MonitorReference) :*: (S1 (MetaSel (Just "downReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Interrupt NoRecovery)) :*: S1 (MetaSel (Just "downProcess") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProcessId))))

data MonitorReference Source #

A value that contains a unique reference of a process monitoring.

Since: 0.12.0

Instances
Eq MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Read MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep MonitorReference :: Type -> Type #

NFData MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: MonitorReference -> () #

type Rep MonitorReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep MonitorReference = D1 (MetaData "MonitorReference" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "MonitorReference" PrefixI True) (S1 (MetaSel (Just "monitorIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "monitoredProcess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)))

type HasSafeProcesses e inner = SetMember Process (Process inner) e Source #

A constraint for an effect set that requires the presence of SafeProcesses.

This constrains the effect list to look like this: [e1 ... eN, Process [e(N+1) .. e(N+k)], e(N+1) .. e(N+k)]

It constrains e to support the (only) Process effect.

This is more relaxed that HasProcesses since it does not require Interrupts.

Since: 0.27.1

type SafeProcesses r = Process r ': r Source #

Cons Process onto a list of effects. This is called SafeProcesses because the the actions cannot be interrupted in.

type HasProcesses e inner = (HasSafeProcesses e inner, Member Interrupts e) Source #

A constraint for an effect set that requires the presence of Processes.

This constrains the effect list to look like this: [e1 ... eN, Interrupts, Process [e(N+1) .. e(N+k)], e(N+1) .. e(N+k)]

It constrains e beyond HasSafeProcesses to encompass Interrupts.

Since: 0.27.1

type Processes e = Interrupts ': SafeProcesses e Source #

This adds a layer of the Interrupts effect on top of Processes

data Interrupt (t :: ExitRecovery) where Source #

A sum-type with reasons for why a process operation, such as receiving messages, is interrupted in the scheduling loop.

This includes errors, that can occur when scheduling messages.

Since: 0.23.0

Constructors

NormalExitRequested :: Interrupt Recoverable

A process has finished a unit of work and might exit or work on something else. This is primarily used for interrupting infinite server loops, allowing for additional cleanup work before exiting (e.g. with ExitNormally)

Since: 0.13.2

NormalExitRequestedWith :: forall a. (Typeable a, Show a, NFData a) => a -> Interrupt Recoverable

Extension of ExitNormally with a custom reason

Since: 0.30.0

OtherProcessNotRunning :: ProcessId -> Interrupt Recoverable

A process that should be running was not running.

TimeoutInterrupt :: String -> Interrupt Recoverable

A Recoverable timeout has occurred.

LinkedProcessCrashed :: ProcessId -> Interrupt Recoverable

A linked process is down, see Link for a discussion on linking.

ErrorInterrupt :: String -> Interrupt Recoverable

An exit reason that has an error message and is Recoverable.

InterruptedBy :: forall a. (Typeable a, Show a, NFData a) => a -> Interrupt Recoverable

An interrupt with a custom message.

Since: 0.30.0

ExitNormally :: Interrupt NoRecovery

A process function returned or exited without any error.

ExitNormallyWith :: forall a. (Typeable a, Show a, NFData a) => a -> Interrupt NoRecovery

A process function returned or exited without any error, and with a custom message

Since: 0.30.0

ExitUnhandledError :: Text -> Interrupt NoRecovery

An error causes the process to exit immediately. For example an unexpected runtime exception was thrown, i.e. an exception derived from SomeException Or a Recoverable Interrupt was not recovered.

ExitProcessCancelled :: Maybe ProcessId -> Interrupt NoRecovery

A process shall exit immediately, without any cleanup was cancelled (e.g. killed, in cancel)

ExitOtherProcessNotRunning :: ProcessId -> Interrupt NoRecovery

A process that is vital to the crashed process was not running

Instances
Eq (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

(==) :: Interrupt x -> Interrupt x -> Bool #

(/=) :: Interrupt x -> Interrupt x -> Bool #

Ord (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Exception (Interrupt Recoverable) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Exception (Interrupt NoRecovery) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData (Interrupt x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: Interrupt x -> () #

(Typeable event, Lifted IO q, Member Logs q) => Server (ObservationQueue event) (Processes q) Source # 
Instance details

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

Associated Types

data StartArgument (ObservationQueue event) :: Type Source #

type Protocol (ObservationQueue event) :: Type Source #

data Model (ObservationQueue event) :: Type Source #

type Settings (ObservationQueue event) :: Type Source #

(IoLogging q, TangibleBroker p, Tangible (ChildId p), Typeable (ServerPdu p), Server p (Processes q), HasProcesses (ServerEffects p (Processes q)) q) => Server (Broker p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

data StartArgument (Broker p) :: Type Source #

type Protocol (Broker p) :: Type Source #

data Model (Broker p) :: Type Source #

type Settings (Broker p) :: Type Source #

(Typeable child, HasPdu (ServerPdu child), Tangible (ChildId child), Ord (ChildId child), Eq (ChildId child), Lifted IO e, Member Logs e) => Server (Watchdog child) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Associated Types

data StartArgument (Watchdog child) :: Type Source #

type Protocol (Watchdog child) :: Type Source #

data Model (Watchdog child) :: Type Source #

type Settings (Watchdog child) :: Type Source #

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

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Associated Types

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

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

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

Methods

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

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

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

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

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

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

data ExitSeverity Source #

This value indicates whether a process exited in way consistent with the planned behaviour or not.

Constructors

NormalExit 
Crash 
Instances
Eq ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ExitSeverity :: Type -> Type #

NFData ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ExitSeverity -> () #

type Rep ExitSeverity Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ExitSeverity = D1 (MetaData "ExitSeverity" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "NormalExit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Crash" PrefixI False) (U1 :: Type -> Type))

data ExitRecovery Source #

This kind is used to indicate if a Interrupt can be treated like a short interrupt which can be handled or ignored.

Constructors

Recoverable 
NoRecovery 
Instances
Eq ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ExitRecovery :: Type -> Type #

NFData ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ExitRecovery -> () #

type Rep ExitRecovery Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ExitRecovery = D1 (MetaData "ExitRecovery" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "Recoverable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoRecovery" PrefixI False) (U1 :: Type -> Type))

data MessageSelector a Source #

A function that decided if the next message will be received by ReceiveSelectedMessage. It conveniently is an instance of Alternative so the message selector can be combined: > > selectInt :: MessageSelector Int > selectInt = selectMessage > > selectString :: MessageSelector String > selectString = selectMessage > > selectIntOrString :: MessageSelector (Either Int String) > selectIntOrString = > Left $ selectTimeout| Right $ selectString

Instances
Functor MessageSelector Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

fmap :: (a -> b) -> MessageSelector a -> MessageSelector b #

(<$) :: a -> MessageSelector b -> MessageSelector a #

Applicative MessageSelector Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Alternative MessageSelector Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Semigroup a => Semigroup (MessageSelector a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Semigroup a => Monoid (MessageSelector a) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

data ResumeProcess v where Source #

Every Process action returns it's actual result wrapped in this type. It will allow to signal errors as well as pass on normal results such as incoming messages.

Constructors

Interrupted :: Interrupt Recoverable -> ResumeProcess v

The current operation of the process was interrupted with a Interrupt. If isRecoverable holds for the given reason, the process may choose to continue.

ResumeWith :: a -> ResumeProcess a

The process may resume to do work, using the given result.

Instances
NFData1 ResumeProcess Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

liftRnf :: (a -> ()) -> ResumeProcess a -> () #

Show v => Show (ResumeProcess v) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic (ResumeProcess v) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep (ResumeProcess v) :: Type -> Type #

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

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ResumeProcess a -> () #

Generic1 ResumeProcess Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep1 ResumeProcess :: k -> Type #

type Rep (ResumeProcess v) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep (ResumeProcess v) = D1 (MetaData "ResumeProcess" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "Interrupted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Interrupt Recoverable))) :+: C1 (MetaCons "ResumeWith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 v)))
type Rep1 ResumeProcess Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep1 ResumeProcess = D1 (MetaData "ResumeProcess" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "Interrupted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Interrupt Recoverable))) :+: C1 (MetaCons "ResumeWith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Serializer message Source #

Serialize a message into a StrictDynamic value to be sent via sendAnyMessage.

This indirection allows, among other things, the composition of Servers.

Since: 0.24.1

Constructors

MkSerializer 

Fields

Instances
Contravariant Serializer Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

contramap :: (a -> b) -> Serializer b -> Serializer a #

(>$) :: b -> Serializer b -> Serializer a #

Typeable message => Show (Serializer message) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

showsPrec :: Int -> Serializer message -> ShowS #

show :: Serializer message -> String #

showList :: [Serializer message] -> ShowS #

NFData (Serializer message) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: Serializer message -> () #

data StrictDynamic Source #

Data flows between Processes via these messages.

This is just a newtype wrapper around Dynamic. The reason this type exists is to force construction through the code in this module, which always evaluates a message to normal form before sending it to another process.

Since: 0.22.0

newtype Timeout Source #

A number of micro seconds.

Since: 0.12.0

Constructors

TimeoutMicros 
Instances
Enum Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Eq Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

(==) :: Timeout -> Timeout -> Bool #

(/=) :: Timeout -> Timeout -> Bool #

Integral Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Num Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Real Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: Timeout -> () #

newtype ProcessDetails Source #

A multi-line text describing the current state of a process for debugging purposes.

Since: 0.24.1

Constructors

MkProcessDetails 
Instances
Eq ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

IsString ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessDetails :: Type -> Type #

Semigroup ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Monoid ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessDetails -> () #

type Rep ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessDetails = D1 (MetaData "ProcessDetails" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" True) (C1 (MetaCons "MkProcessDetails" PrefixI True) (S1 (MetaSel (Just "_fromProcessDetails") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype ProcessTitle Source #

A short title for a Process for logging purposes.

Since: 0.24.1

Constructors

MkProcessTitle 
Instances
Eq ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

IsString ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessTitle :: Type -> Type #

Semigroup ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Monoid ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessTitle -> () #

type Rep ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessTitle = D1 (MetaData "ProcessTitle" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" True) (C1 (MetaCons "MkProcessTitle" PrefixI True) (S1 (MetaSel (Just "_fromProcessTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Process (r :: [Type -> Type]) b where Source #

The process effect is the basis for message passing concurrency. This effect describes an interface for concurrent, communicating isolated processes identified uniquely by a process-id.

Processes can raise exceptions that can be caught, exit gracefully or with an error, or be killed by other processes, with the option of ignoring the shutdown request.

Process Scheduling is implemented in different modules. All scheduler implementations should follow some basic rules:

  • fair scheduling
  • sending a message does not block
  • receiving a message does block
  • spawning a child blocks only a very moment
  • a newly spawned process shall be scheduled before the parent process after
  • the spawnRaw
  • when the first process exists, all process should be killed immediately

Constructors

FlushMessages :: Process r (ResumeProcess [StrictDynamic])

Remove all messages from the process' message queue

YieldProcess :: Process r (ResumeProcess ())

In cooperative schedulers, this will give processing time to the scheduler. Every other operation implicitly serves the same purpose.

Since: 0.12.0

Delay :: Timeout -> Process r (ResumeProcess ())

Simply wait until the time in the given Timeout has elapsed and return.

Since: 0.30.0

SelfPid :: Process r (ResumeProcess ProcessId)

Return the current ProcessId

Spawn :: ProcessTitle -> Eff (Process r ': r) () -> Process r (ResumeProcess ProcessId)

Start a new process, the new process will execute an effect, the function will return immediately with a ProcessId.

SpawnLink :: ProcessTitle -> Eff (Process r ': r) () -> Process r (ResumeProcess ProcessId)

Start a new process, and Link to it .

Since: 0.12.0

Shutdown :: Interrupt NoRecovery -> Process r a

Shutdown the process; irregardless of the exit reason, this function never returns,

SendShutdown :: ProcessId -> Interrupt NoRecovery -> Process r (ResumeProcess ())

Shutdown another process immediately, the other process has no way of handling this!

SendInterrupt :: ProcessId -> Interrupt Recoverable -> Process r (ResumeProcess ())

Request that another a process interrupts. The targeted process is interrupted and gets an Interrupted, the target process may decide to ignore the interrupt and continue as if nothing happened.

SendMessage :: ProcessId -> StrictDynamic -> Process r (ResumeProcess ())

Send a message to a process addressed by the ProcessId. Sending a message should always succeed and return immediately, even if the destination process does not exist, or does not accept messages of the given type.

ReceiveSelectedMessage :: forall r a. MessageSelector a -> Process r (ResumeProcess a)

Receive a message that matches a criteria. This should block until an a message was received. The message is returned as a ResumeProcess value. The function should also return if an exception was caught or a shutdown was requested.

MakeReference :: Process r (ResumeProcess Int)

Generate a unique Int for the current process.

Monitor :: ProcessId -> Process r (ResumeProcess MonitorReference)

Monitor another process. When the monitored process exits a ProcessDown is sent to the calling process. The return value is a unique identifier for that monitor. There can be multiple monitors on the same process, and a message for each will be sent. If the process is already dead, the ProcessDown message will be sent immediately, without exit reason

Since: 0.12.0

Demonitor :: MonitorReference -> Process r (ResumeProcess ())

Remove a monitor.

Since: 0.12.0

Link :: ProcessId -> Process r (ResumeProcess ())

Connect the calling process to another process, such that if one of the processes crashes (i.e. isCrash returns True), the other is shutdown with the Interrupt LinkedProcessCrashed.

You might wonder: Why not tearing down the linked process when exiting normally? I thought about this. If a process exits normally, it should have the opportunity to shutdown stuff explicitly. And if you want to make sure that there are no dangling child processes after e.g. a broker crash, you can always use monitor.

Since: 0.12.0

Unlink :: ProcessId -> Process r (ResumeProcess ())

Unlink the calling process from the other process.

See Link for a discussion on linking.

Since: 0.12.0

UpdateProcessDetails :: ProcessDetails -> Process r (ResumeProcess ())

Update the ProcessDetails of a process

GetProcessState :: ProcessId -> Process r (ResumeProcess (Maybe (ProcessTitle, ProcessDetails, ProcessState)))

Get the ProcessState (or Nothing if the process is dead)

Instances
(Typeable event, Lifted IO q, Member Logs q) => Server (ObservationQueue event) (Processes q) Source # 
Instance details

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

Associated Types

data StartArgument (ObservationQueue event) :: Type Source #

type Protocol (ObservationQueue event) :: Type Source #

data Model (ObservationQueue event) :: Type Source #

type Settings (ObservationQueue event) :: Type Source #

(IoLogging q, TangibleBroker p, Tangible (ChildId p), Typeable (ServerPdu p), Server p (Processes q), HasProcesses (ServerEffects p (Processes q)) q) => Server (Broker p) (Processes q) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

data StartArgument (Broker p) :: Type Source #

type Protocol (Broker p) :: Type Source #

data Model (Broker p) :: Type Source #

type Settings (Broker p) :: Type Source #

(Typeable child, HasPdu (ServerPdu child), Tangible (ChildId child), Ord (ChildId child), Eq (ChildId child), Lifted IO e, Member Logs e) => Server (Watchdog child) (Processes e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Associated Types

data StartArgument (Watchdog child) :: Type Source #

type Protocol (Watchdog child) :: Type Source #

data Model (Watchdog child) :: Type Source #

type Settings (Watchdog child) :: Type Source #

Show (Process r b) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

showsPrec :: Int -> Process r b -> ShowS #

show :: Process r b -> String #

showList :: [Process r b] -> ShowS #

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

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

Associated Types

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

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

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

Methods

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

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

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

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

Defined in Control.Eff.Concurrent.Protocol.CallbackServer

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

fromProcessTitle :: Lens' ProcessTitle Text Source #

An isomorphism lens for the ProcessTitle

Since: 0.24.1

fromProcessDetails :: Lens' ProcessDetails Text Source #

An isomorphism lens for the ProcessDetails

Since: 0.24.1

toStrictDynamic :: (Typeable a, NFData a) => a -> StrictDynamic Source #

Deeply evaluate the given value and wrap it into a StrictDynamic.

Since: 0.22.0

fromStrictDynamic :: Typeable a => StrictDynamic -> Maybe a Source #

Convert a StrictDynamic back to a value.

Since: 0.22.0

unwrapStrictDynamic :: StrictDynamic -> Dynamic Source #

Convert a StrictDynamic back to an unwrapped Dynamic.

Since: 0.22.0

selectMessage :: Typeable t => MessageSelector t Source #

Create a message selector for a value that can be obtained by fromStrictDynamic.

Since: 0.9.1

filterMessage :: Typeable a => (a -> Bool) -> MessageSelector a Source #

Create a message selector from a predicate.

Since: 0.9.1

selectMessageWith :: Typeable a => (a -> Maybe b) -> MessageSelector b Source #

Select a message of type a and apply the given function to it. If the function returns Just The ReceiveSelectedMessage function will return the result (sans Maybe).

Since: 0.9.1

selectDynamicMessage :: (StrictDynamic -> Maybe a) -> MessageSelector a Source #

Create a message selector.

Since: 0.9.1

selectAnyMessage :: MessageSelector StrictDynamic Source #

Create a message selector that will match every message. This is lazy because the result is not forceed.

Since: 0.9.1

isProcessDownInterrupt :: Maybe ProcessId -> Interrupt r -> Bool Source #

A predicate for linked process crashes.

provideInterruptsShutdown :: forall e a. Eff (Processes e) a -> Eff (SafeProcesses e) a Source #

Handle all Interrupts of an Processes by wrapping them up in interruptToExit and then do a process Shutdown.

handleInterrupts :: (HasCallStack, Member Interrupts r) => (Interrupt Recoverable -> Eff r a) -> Eff r a -> Eff r a Source #

Handle Interrupts arising during process operations, e.g. when a linked process crashes while we wait in a receiveSelectedMessage via a call to interrupt.

tryUninterrupted :: (HasCallStack, Member Interrupts r) => Eff r a -> Eff r (Either (Interrupt Recoverable) a) Source #

Like handleInterrupts, but instead of passing the Interrupt to a handler function, Either is returned.

Since: 0.13.2

logInterrupts :: forall r. (Member Logs r, HasCallStack, Member Interrupts r) => Eff r () -> Eff r () Source #

Handle interrupts by logging them with logProcessExit and otherwise ignoring them.

exitOnInterrupt :: (HasCallStack, HasProcesses r q) => Eff r a -> Eff r a Source #

Handle Interrupts arising during process operations, e.g. when a linked process crashes while we wait in a receiveSelectedMessage via a call to interrupt.

provideInterrupts :: HasCallStack => Eff (Interrupts ': r) a -> Eff r (Either (Interrupt Recoverable) a) Source #

Handle Interrupts arising during process operations, e.g. when a linked process crashes while we wait in a receiveSelectedMessage via a call to interrupt.

isCrash :: Interrupt x -> Bool Source #

A predicate for crashes. A crash happens when a process exits with an Interrupt other than ExitNormally

isRecoverable :: Interrupt x -> Bool Source #

A predicate for recoverable exit reasons. This predicate defines the exit reasons which functions such as executeAndResume

toCrashReason :: Interrupt x -> Maybe Text Source #

Print a Interrupt to Just a formatted String when isCrash is True. This can be useful in combination with view patterns, e.g.:

logCrash :: Interrupt -> Eff e ()
logCrash (toCrashReason -> Just reason) = logError reason
logCrash _ = return ()

Though this can be improved to:

logCrash = traverse_ logError . toCrashReason

logProcessExit :: forall e x. (Member Logs e, HasCallStack) => Interrupt x -> Eff e () Source #

Log the Interrupts

executeAndResume :: forall q r v. (HasSafeProcesses r q, HasCallStack) => Process q (ResumeProcess v) -> Eff r (Either (Interrupt Recoverable) v) Source #

Execute a and action and return the result; if the process is interrupted by an error or exception, or an explicit shutdown from another process, or through a crash of a linked process, i.e. whenever the exit reason satisfies isRecoverable, return the exit reason.

executeAndResumeOrExit :: forall r q v. (HasSafeProcesses r q, HasCallStack) => Process q (ResumeProcess v) -> Eff r v Source #

Execute a Process action and resume the process, exit the process when an Interrupts was raised. Use executeAndResume to catch interrupts.

executeAndResumeOrThrow :: forall q r v. (HasProcesses r q, HasCallStack) => Process q (ResumeProcess v) -> Eff r v Source #

Execute a Process action and resume the process, exit the process when an Interrupts was raised. Use executeAndResume to catch interrupts.

yieldProcess :: forall r q. (HasProcesses r q, HasCallStack) => Eff r () Source #

Use executeAndResumeOrExit to execute YieldProcess. Refer to YieldProcess for more information.

delay :: forall r q. (HasProcesses r q, HasCallStack) => Timeout -> Eff r () Source #

Simply block until the time in the Timeout has passed.

Since: 0.30.0

sendMessage :: forall o r q. (HasProcesses r q, HasCallStack, Typeable o, NFData o) => ProcessId -> o -> Eff r () Source #

Send a message to a process addressed by the ProcessId. See SendMessage.

The message will be reduced to normal form (rnf) by/in the caller process.

sendAnyMessage :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> StrictDynamic -> Eff r () Source #

Send a Dynamic value to a process addressed by the ProcessId. See SendMessage.

sendShutdown :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Interrupt NoRecovery -> Eff r () Source #

Exit a process addressed by the ProcessId. The process will exit, it might do some cleanup, but is ultimately unrecoverable. See SendShutdown.

sendInterrupt :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Interrupt Recoverable -> Eff r () Source #

Interrupts a process addressed by the ProcessId. The process might exit, or it may continue. | Like sendInterrupt, but also return True iff the process to exit exists.

spawn :: forall r q. (HasCallStack, HasProcesses r q) => ProcessTitle -> Eff (Processes q) () -> Eff r ProcessId Source #

Start a new process, the new process will execute an effect, the function will return immediately with a ProcessId. If the new process is interrupted, the process will Shutdown with the Interrupt wrapped in interruptToExit. For specific use cases it might be better to use spawnRaw.

spawn_ :: forall r q. (HasCallStack, HasProcesses r q) => ProcessTitle -> Eff (Processes q) () -> Eff r () Source #

Like spawn but return ().

spawnLink :: forall r q. (HasCallStack, HasProcesses r q) => ProcessTitle -> Eff (Processes q) () -> Eff r ProcessId Source #

Start a new process, and immediately link to it.

See Link for a discussion on linking.

Since: 0.12.0

spawnRaw :: forall r q. (HasCallStack, HasProcesses r q) => ProcessTitle -> Eff (SafeProcesses q) () -> Eff r ProcessId Source #

Start a new process, the new process will execute an effect, the function will return immediately with a ProcessId. The spawned process has only the raw SafeProcesses effects. For non-library code spawn might be better suited.

spawnRaw_ :: forall r q. (HasCallStack, HasProcesses r q) => ProcessTitle -> Eff (SafeProcesses q) () -> Eff r () Source #

Like spawnRaw but return ().

isProcessAlive :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Eff r Bool Source #

Return True if the process is alive.

Since: 0.12.0

getProcessState :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Eff r (Maybe (ProcessTitle, ProcessDetails, ProcessState)) Source #

Return the ProcessTitle, ProcessDetails and ProcessState, for the given process, if the process is alive.

Since: 0.24.1

updateProcessDetails :: forall r q. (HasCallStack, HasProcesses r q) => ProcessDetails -> Eff r () Source #

Replace the ProcessDetails of the process.

Since: 0.24.1

receiveAnyMessage :: forall r q. (HasCallStack, HasProcesses r q) => Eff r StrictDynamic Source #

Block until a message was received. See ReceiveSelectedMessage for more documentation.

receiveSelectedMessage :: forall r q a. (HasCallStack, Show a, HasProcesses r q) => MessageSelector a -> Eff r a Source #

Block until a message was received, that is not Nothing after applying a callback to it. See ReceiveSelectedMessage for more documentation.

receiveMessage :: forall a r q. (HasCallStack, Typeable a, NFData a, Show a, HasProcesses r q) => Eff r a Source #

Receive and cast the message to some Typeable instance. See ReceiveSelectedMessage for more documentation. This will wait for a message of the return type using receiveSelectedMessage

flushMessages :: forall r q. (HasCallStack, HasProcesses r q) => Eff r [StrictDynamic] Source #

Remove and return all messages currently enqueued in the process message queue.

Since: 0.12.0

receiveSelectedLoop :: forall r q a endOfLoopResult. (HasSafeProcesses r q, HasCallStack) => MessageSelector a -> (Either (Interrupt Recoverable) a -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

Enter a loop to receive messages and pass them to a callback, until the function returns Just a result. Only the messages of the given type will be received. If the process is interrupted by an exception of by a SendShutdown from another process, with an exit reason that satisfies isRecoverable, then the callback will be invoked with Left Interrupt, otherwise the process will be exited with the same reason using exitBecause. See also ReceiveSelectedMessage for more documentation.

receiveAnyLoop :: forall r q endOfLoopResult. (HasSafeProcesses r q, HasCallStack) => (Either (Interrupt Recoverable) StrictDynamic -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

Like receiveSelectedLoop but not selective. See also selectAnyMessage, receiveSelectedLoop.

receiveLoop :: forall r q a endOfLoopResult. (HasSafeProcesses r q, HasCallStack, NFData a, Typeable a) => (Either (Interrupt Recoverable) a -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

Like receiveSelectedLoop but refined to casting to a specific Typeable using selectMessage.

self :: (HasCallStack, HasSafeProcesses r q) => Eff r ProcessId Source #

Returns the ProcessId of the current process.

makeReference :: (HasCallStack, HasProcesses r q) => Eff r Int Source #

Generate a unique Int for the current process.

monitor :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Eff r MonitorReference Source #

Monitor another process. When the monitored process exits a ProcessDown is sent to the calling process. The return value is a unique identifier for that monitor. There can be multiple monitors on the same process, and a message for each will be sent. If the process is already dead, the ProcessDown message will be sent immediately, without exit reason

Since: 0.12.0

demonitor :: forall r q. (HasCallStack, HasProcesses r q) => MonitorReference -> Eff r () Source #

Remove a monitor created with monitor.

Since: 0.12.0

withMonitor :: (HasCallStack, HasProcesses r q) => ProcessId -> (MonitorReference -> Eff r a) -> Eff r a Source #

monitor another process before while performing an action and demonitor afterwards.

Since: 0.12.0

receiveWithMonitor :: (HasCallStack, HasProcesses r q, Typeable a, Show a) => ProcessId -> MessageSelector a -> Eff r (Either ProcessDown a) Source #

A MessageSelector for receiving either a monitor of the given process or another message.

Since: 0.12.0

becauseProcessIsDown :: ProcessDown -> Interrupt Recoverable Source #

Make an Interrupt for a ProcessDown message.

For example: doSomething >>= either (interrupt . becauseProcessIsDown) return

Since: 0.12.0

selectProcessDown :: MonitorReference -> MessageSelector ProcessDown Source #

A MessageSelector for the ProcessDown message of a specific process.

The parameter is the value obtained by monitor.

Since: 0.12.0

selectProcessDownByProcessId :: ProcessId -> MessageSelector ProcessDown Source #

A MessageSelector for the ProcessDown message. of a specific process.

In contrast to selectProcessDown this function matches the ProcessId.

Since: 0.28.0

linkProcess :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Eff r () Source #

Connect the calling process to another process, such that if one of the processes crashes (i.e. isCrash returns True), the other is shutdown with the Interrupt LinkedProcessCrashed.

See Link for a discussion on linking.

Since: 0.12.0

unlinkProcess :: forall r q. (HasCallStack, HasProcesses r q) => ProcessId -> Eff r () Source #

Unlink the calling process from the other process.

See Link for a discussion on linking.

Since: 0.12.0

exitBecause :: forall r q a. (HasCallStack, HasSafeProcesses r q) => Interrupt NoRecovery -> Eff r a Source #

Exit the process with a Interrupt.

exitNormally :: forall r q a. (HasCallStack, HasSafeProcesses r q) => Eff r a Source #

Exit the process.

exitWithError :: forall r q a. (HasCallStack, HasSafeProcesses r q) => String -> Eff r a Source #

Exit the process with an error.

data Receiver a Source #

A ProcessId and a Serializer. EXPERIMENTAL

See sendToReceiver.

Since: 0.29.0

Constructors

(NFData out, Typeable out, Show out) => Receiver 
Instances
Contravariant Receiver Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

contramap :: (a -> b) -> Receiver b -> Receiver a #

(>$) :: b -> Receiver b -> Receiver a #

Eq (Receiver o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

(==) :: Receiver o -> Receiver o -> Bool #

(/=) :: Receiver o -> Receiver o -> Bool #

Ord (Receiver o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

compare :: Receiver o -> Receiver o -> Ordering #

(<) :: Receiver o -> Receiver o -> Bool #

(<=) :: Receiver o -> Receiver o -> Bool #

(>) :: Receiver o -> Receiver o -> Bool #

(>=) :: Receiver o -> Receiver o -> Bool #

max :: Receiver o -> Receiver o -> Receiver o #

min :: Receiver o -> Receiver o -> Receiver o #

Typeable protocol => Show (Receiver protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

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

show :: Receiver protocol -> String #

showList :: [Receiver protocol] -> ShowS #

NFData (Receiver o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: Receiver o -> () #

sendToReceiver :: (NFData o, HasProcesses r q) => Receiver o -> o -> Eff r () Source #

Serialize and send a message to the process in a Receiver.

EXPERIMENTAL

Since: 0.29.0

Scheduler Process Effect Handler

Concurrent Scheduler

type BaseEffects = Reader SchedulerState ': LoggingAndIo Source #

The concrete list of Effects for this scheduler implementation.

Since: 0.25.0

type HasBaseEffects r = (HasCallStack, Lifted IO r, BaseEffects <:: r) Source #

Type class constraint to indicate that an effect union contains the effects required by every process and the scheduler implementation itself.

Since: 0.25.0

type Effects = Processes BaseEffects Source #

The Effects for interruptable, concurrent processes, scheduled via forkIO.

Since: 0.25.0

type SafeEffects = SafeProcesses BaseEffects Source #

The concrete list of Effects of processes compatible with this scheduler. This builds upon BaseEffects.

Since: 0.25.0

defaultMain :: HasCallStack => Eff Effects () -> IO () Source #

Start the message passing concurrency system then execute a Process on top of BaseEffects effect. All logging is sent to standard output.

defaultMainWithLogWriter :: HasCallStack => LogWriter -> Eff Effects () -> IO () Source #

Start the message passing concurrency system then execute a Process on top of BaseEffects effect. All logging is sent to standard output.

schedule :: HasCallStack => Eff Effects () -> Eff LoggingAndIo () Source #

This is the main entry point to running a message passing concurrency application. This function takes a Process on top of the BaseEffects effect for concurrent logging.

Timers and Timeouts

data TimerReference Source #

The reference to a timer started by startTimer, required to stop a timer via cancelTimer.

Since: 0.12.0

Instances
Enum TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Eq TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Integral TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Num TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Ord TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Real TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Show TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

NFData TimerReference Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Methods

rnf :: TimerReference -> () #

receiveAfter :: forall a r q. (HasCallStack, HasProcesses r q, Typeable a, NFData a, Show a) => Timeout -> Eff r (Maybe a) Source #

Wait for a message of the given type for the given time. When no message arrives in time, return Nothing. This is based on receiveSelectedAfter.

Since: 0.12.0

receiveSelectedAfter :: forall a r q. (HasCallStack, HasProcesses r q, Show a, Typeable a) => MessageSelector a -> Timeout -> Eff r (Either TimerElapsed a) Source #

Wait for a message of the given type for the given time. When no message arrives in time, return Left TimerElapsed. This is based on selectTimerElapsed and startTimer.

Since: 0.12.0

receiveAfterWithTitle :: forall a r q. (HasCallStack, HasProcesses r q, Typeable a, NFData a, Show a) => Timeout -> ProcessTitle -> Eff r (Maybe a) Source #

Wait for a message of the given type for the given time. When no message arrives in time, return Nothing. This is based on receiveSelectedAfterWithTitle.

Since: 0.12.0

receiveSelectedAfterWithTitle :: forall a r q. (HasCallStack, HasProcesses r q, Show a, Typeable a) => MessageSelector a -> Timeout -> ProcessTitle -> Eff r (Either TimerElapsed a) Source #

Wait for a message of the given type for the given time. When no message arrives in time, return Left TimerElapsed. This is based on selectTimerElapsed and startTimerWithTitle.

Since: 0.12.0

receiveSelectedWithMonitorAfterWithTitle :: forall a r q. (HasCallStack, HasProcesses r q, Show a, Typeable a) => ProcessId -> MessageSelector a -> Timeout -> ProcessTitle -> Eff r (Either (Either ProcessDown TimerElapsed) a) Source #

Like receiveWithMonitorWithTitle combined with receiveSelectedAfterWithTitle.

Since: 0.30.0

sendAfter :: forall r q message. (HasCallStack, HasProcesses r q, Typeable message, NFData message) => ProcessId -> Timeout -> (TimerReference -> message) -> Eff r TimerReference Source #

Send a message to a given process after waiting. The message is created by applying the function parameter to the TimerReference, such that the message can directly refer to the timer.

Since: 0.12.0

sendAfterWithTitle :: forall r q message. (HasCallStack, HasProcesses r q, Typeable message, NFData message) => ProcessTitle -> ProcessId -> Timeout -> (TimerReference -> message) -> Eff r TimerReference Source #

Like sendAfter but with a user provided name for the timer process.

Since: 0.30.0

startTimerWithTitle :: forall r q. (HasCallStack, HasProcesses r q) => ProcessTitle -> Timeout -> Eff r TimerReference Source #

Start a new timer, after the time has elapsed, TimerElapsed is sent to calling process. The message also contains the TimerReference returned by this function. Use cancelTimer to cancel the timer. Use selectTimerElapsed to receive the message using receiveSelectedMessage. To receive messages with guarded with a timeout see receiveAfter.

This calls sendAfterWithTitle under the hood with TimerElapsed as message.

Since: 0.30.0

startTimer :: forall r q. (HasCallStack, HasProcesses r q) => Timeout -> Eff r TimerReference Source #

Start a new timer, after the time has elapsed, TimerElapsed is sent to calling process. The message also contains the TimerReference returned by this function. Use cancelTimer to cancel the timer. Use selectTimerElapsed to receive the message using receiveSelectedMessage. To receive messages with guarded with a timeout see receiveAfter.

Calls sendAfter under the hood.

Since: 0.12.0

cancelTimer :: forall r q. (HasCallStack, HasProcesses r q) => TimerReference -> Eff r () Source #

Cancel a timer started with startTimer.

Since: 0.12.0

Data Types and Functions for APIs (aka Protocols)

class (Typeable protocol, Typeable embeddedProtocol) => HasPduPrism protocol embeddedProtocol where Source #

A class for Pdu instances that embed other Pdu.

This is a part of Embeds provide instances for your Pdus but in client code use the Embeds constraint.

Instances of this class serve as proof to Embeds that a conversion into another Pdu actually exists.

A Prism for the embedded Pdu is the center of this class

Laws: embeddedPdu = prism' embedPdu fromPdu

Since: 0.29.0

Minimal complete definition

Nothing

Methods

embeddedPdu :: forall (result :: Synchronicity). Prism' (Pdu protocol result) (Pdu embeddedProtocol result) Source #

A Prism for the embedded Pdus.

embedPdu :: forall (result :: Synchronicity). Pdu embeddedProtocol result -> Pdu protocol result Source #

Embed the Pdu value of an embedded protocol into the corresponding Pdu value.

fromPdu :: forall (result :: Synchronicity). Pdu protocol result -> Maybe (Pdu embeddedProtocol result) Source #

Examine a Pdu value from the outer protocol, and return it, if it embeds a Pdu of embedded protocol, otherwise return Nothing/

Instances
Typeable a => HasPduPrism a a Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu a result) (Pdu a result) Source #

embedPdu :: Pdu a result -> Pdu a result Source #

fromPdu :: Pdu a result -> Maybe (Pdu a result) Source #

Typeable p => HasPduPrism (Broker p) (ObserverRegistry (ChildEvent p)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

embeddedPdu :: Prism' (Pdu (Broker p) result) (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

embedPdu :: Pdu (ObserverRegistry (ChildEvent p)) result -> Pdu (Broker p) result Source #

fromPdu :: Pdu (Broker p) result -> Maybe (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

Typeable child => HasPduPrism (Watchdog child) (Observer (ChildEvent child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

embeddedPdu :: Prism' (Pdu (Watchdog child) result) (Pdu (Observer (ChildEvent child)) result) Source #

embedPdu :: Pdu (Observer (ChildEvent child)) result -> Pdu (Watchdog child) result Source #

fromPdu :: Pdu (Watchdog child) result -> Maybe (Pdu (Observer (ChildEvent child)) result) Source #

(Typeable a1, Typeable a2) => HasPduPrism (a1, a2) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 result -> Pdu (a1, a2) result Source #

fromPdu :: Pdu (a1, a2) result -> Maybe (Pdu a2 result) Source #

(Typeable a1, Typeable a2) => HasPduPrism (a1, a2) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 result -> Pdu (a1, a2) result Source #

fromPdu :: Pdu (a1, a2) result -> Maybe (Pdu a1 result) Source #

(Typeable a1, Typeable a2, Typeable a3) => HasPduPrism (a1, a2, a3) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 result -> Pdu (a1, a2, a3) result Source #

fromPdu :: Pdu (a1, a2, a3) result -> Maybe (Pdu a3 result) Source #

(Typeable a1, Typeable a2, Typeable a3) => HasPduPrism (a1, a2, a3) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 result -> Pdu (a1, a2, a3) result Source #

fromPdu :: Pdu (a1, a2, a3) result -> Maybe (Pdu a2 result) Source #

(Typeable a1, Typeable a2, Typeable a3) => HasPduPrism (a1, a2, a3) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 result -> Pdu (a1, a2, a3) result Source #

fromPdu :: Pdu (a1, a2, a3) result -> Maybe (Pdu a1 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (a1, a2, a3, a4) a4 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a4 result) Source #

embedPdu :: Pdu a4 result -> Pdu (a1, a2, a3, a4) result Source #

fromPdu :: Pdu (a1, a2, a3, a4) result -> Maybe (Pdu a4 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (a1, a2, a3, a4) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 result -> Pdu (a1, a2, a3, a4) result Source #

fromPdu :: Pdu (a1, a2, a3, a4) result -> Maybe (Pdu a3 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (a1, a2, a3, a4) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 result -> Pdu (a1, a2, a3, a4) result Source #

fromPdu :: Pdu (a1, a2, a3, a4) result -> Maybe (Pdu a2 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPduPrism (a1, a2, a3, a4) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 result -> Pdu (a1, a2, a3, a4) result Source #

fromPdu :: Pdu (a1, a2, a3, a4) result -> Maybe (Pdu a1 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (a1, a2, a3, a4, a5) a5 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a5 result) Source #

embedPdu :: Pdu a5 result -> Pdu (a1, a2, a3, a4, a5) result Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) result -> Maybe (Pdu a5 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (a1, a2, a3, a4, a5) a4 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a4 result) Source #

embedPdu :: Pdu a4 result -> Pdu (a1, a2, a3, a4, a5) result Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) result -> Maybe (Pdu a4 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (a1, a2, a3, a4, a5) a3 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a3 result) Source #

embedPdu :: Pdu a3 result -> Pdu (a1, a2, a3, a4, a5) result Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) result -> Maybe (Pdu a3 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (a1, a2, a3, a4, a5) a2 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a2 result) Source #

embedPdu :: Pdu a2 result -> Pdu (a1, a2, a3, a4, a5) result Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) result -> Maybe (Pdu a2 result) Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPduPrism (a1, a2, a3, a4, a5) a1 Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

embeddedPdu :: Prism' (Pdu (a1, a2, a3, a4, a5) result) (Pdu a1 result) Source #

embedPdu :: Pdu a1 result -> Pdu (a1, a2, a3, a4, a5) result Source #

fromPdu :: Pdu (a1, a2, a3, a4, a5) result -> Maybe (Pdu a1 result) Source #

type family ProtocolReply (s :: Synchronicity) where ... Source #

This type function takes an Pdu and analysis the reply type, i.e. the Synchronicity and evaluates to either t for an Pdu x (Synchronous t) or to '()' for an Pdu x Asynchronous.

Since: 0.24.0

data Synchronicity Source #

The (promoted) constructors of this type specify (at the type level) the reply behavior of a specific constructor of an Pdu instance.

Constructors

Synchronous Type

Specify that handling a request is a blocking operation with a specific return type, e.g. ('Synchronous (Either RentalError RentalId))

Asynchronous

Non-blocking, asynchronous, request handling

type TangiblePdu p r = (Typeable p, Typeable r, Tangible (Pdu p r), HasPdu p) Source #

A Constraint that bundles the requirements for the Pdu values of a protocol.

This ensures that Pdus can be strictly and deeply evaluated and shown such that for example logging is possible.

Since: 0.24.0

type Tangible i = (NFData i, Typeable i, Show i) Source #

A set of constraints for types that can evaluated via NFData, compared via Ord and presented dynamically via Typeable, and represented both as values via Show.

Since: 0.23.0

type Embeds outer inner = (HasPduPrism outer inner, CheckEmbeds outer inner, HasPdu outer) Source #

A constraint that requires that the outer Pdu has a clause to embed values from the inner Pdu.

Also, this constraint requires a HasPduPrism instance, as a proof for a possible conversion of an embedded Pdu value into to the enclosing Pdu.

This generates better compiler error messages, when an embedding of a Pdu into another.

This is provided by HasPdu instances. The instances are required to provide a list of embedded Pdu values in EmbeddedPduList.

Note that every type embeds itself, so Embeds x x always holds.

Since: 0.29.1

class Typeable protocol => HasPdu (protocol :: Type) Source #

This type class and the associated data family defines the protocol data units (PDU) of a protocol.

A Protocol in the sense of a communication interface description between processes.

The first parameter is usually a user defined type that identifies the protocol that uses the Pdus are. It maybe a phantom type.

The second parameter specifies if a specific constructor of an (GADT-like) Pdu instance is Synchronous, i.e. returns a result and blocks the caller or if it is Asynchronous

Example:

data BookShop deriving Typeable

instance Typeable r => HasPdu BookShop r where
  data instance Pdu BookShop r where
    RentBook  :: BookId   -> Pdu BookShop ('Synchronous (Either RentalError RentalId))
    BringBack :: RentalId -> Pdu BookShop 'Asynchronous
    deriving Typeable

type BookId = Int
type RentalId = Int
type RentalError = String

Since: 0.25.1

Associated Types

type EmbeddedPduList protocol :: [Type] Source #

A type level list Protocol phantom types included in the associated Pdu instance.

This is just a helper for better compiler error messages. It relies on Embeds to add the constraint HasPduPrism.

Since: 0.29.0

data Pdu protocol (reply :: Synchronicity) Source #

The protocol data unit type for the given protocol.

Instances
Tangible event => HasPdu (ObserverRegistry event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (ObserverRegistry event) :: [Type] Source #

data Pdu (ObserverRegistry event) reply :: Type Source #

Typeable p => HasPdu (Broker p) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Associated Types

type EmbeddedPduList (Broker p) :: [Type] Source #

data Pdu (Broker p) reply :: Type Source #

Typeable child => HasPdu (Watchdog child) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Associated Types

type EmbeddedPduList (Watchdog child) :: [Type] Source #

data Pdu (Watchdog child) reply :: Type Source #

(HasPdu a1, HasPdu a2) => HasPdu (a1, a2) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2) :: [Type] Source #

data Pdu (a1, a2) reply :: Type Source #

Tangible event => HasPdu (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (Observer event) :: [Type] Source #

data Pdu (Observer event) reply :: Type Source #

(HasPdu a1, HasPdu a2, HasPdu a3) => HasPdu (a1, a2, a3) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2, a3) :: [Type] Source #

data Pdu (a1, a2, a3) reply :: Type Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4) => HasPdu (a1, a2, a3, a4) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2, a3, a4) :: [Type] Source #

data Pdu (a1, a2, a3, a4) reply :: Type Source #

(HasPdu a1, HasPdu a2, HasPdu a3, HasPdu a4, HasPdu a5) => HasPdu (a1, a2, a3, a4, a5) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Associated Types

type EmbeddedPduList (a1, a2, a3, a4, a5) :: [Type] Source #

data Pdu (a1, a2, a3, a4, a5) reply :: Type Source #

newtype Endpoint protocol Source #

A server process for protocol.

Protocols are represented by phantom types, which are used in different places to index type families and type class instances.

A Process can send and receive any messages. An Endpoint wraps around a ProcessId and carries a phantom type to indicate the kinds of messages accepted by the process.

As a metaphor, communication between processes can be thought of waiting for and sending protocol data units belonging to some protocol.

Constructors

Endpoint 
Instances
Eq (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

(==) :: Endpoint protocol -> Endpoint protocol -> Bool #

(/=) :: Endpoint protocol -> Endpoint protocol -> Bool #

Ord (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

compare :: Endpoint protocol -> Endpoint protocol -> Ordering #

(<) :: Endpoint protocol -> Endpoint protocol -> Bool #

(<=) :: Endpoint protocol -> Endpoint protocol -> Bool #

(>) :: Endpoint protocol -> Endpoint protocol -> Bool #

(>=) :: Endpoint protocol -> Endpoint protocol -> Bool #

max :: Endpoint protocol -> Endpoint protocol -> Endpoint protocol #

min :: Endpoint protocol -> Endpoint protocol -> Endpoint protocol #

Typeable protocol => Show (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

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

show :: Endpoint protocol -> String #

showList :: [Endpoint protocol] -> ShowS #

NFData (Endpoint protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Endpoint protocol -> () #

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

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Endpoint a :: Type) = ToPretty a <+> PutStr "endpoint"

proxyAsEndpoint :: proxy protocol -> ProcessId -> Endpoint protocol Source #

Tag a ProcessId with an Pdu type index to mark it a Endpoint process handling that API

asEndpoint :: forall protocol. ProcessId -> Endpoint protocol Source #

Tag a ProcessId with an Pdu type index to mark it a Endpoint process handling that API

toEmbeddedEndpoint :: forall inner outer. Embeds outer inner => Endpoint outer -> Endpoint inner Source #

Convert an Endpoint to an endpoint for an embedded protocol.

See Embeds, fromEmbeddedEndpoint.

Since: 0.25.1

fromEmbeddedEndpoint :: forall outer inner. HasPduPrism outer inner => Endpoint inner -> Endpoint outer Source #

Convert an Endpoint to an endpoint for a server, that embeds the protocol.

See Embeds, toEmbeddedEndpoint.

Since: 0.25.1

fromEndpoint :: forall protocol protocol. Iso (Endpoint protocol) (Endpoint protocol) ProcessId ProcessId Source #

Client Functions for Consuming APIs

type EndpointReader o = Reader (Endpoint o) Source #

The reader effect for ProcessIds for Pdus, see runEndpointReader

type HasEndpointReader o r = (Typeable o, Member (EndpointReader o) r) Source #

Instead of passing around a Endpoint value and passing to functions like cast or call, a Endpoint can provided by a Reader effect, if there is only a single server for a given Pdu instance. This type alias is convenience to express that an effect has Process and a reader for a Endpoint.

cast :: forall destination protocol r q. (HasCallStack, HasProcesses r q, HasPdu destination, HasPdu protocol, Tangible (Pdu destination Asynchronous), Embeds destination protocol) => Endpoint destination -> Pdu protocol Asynchronous -> Eff r () Source #

Send a request Pdu that has no reply and return immediately.

The type signature enforces that the corresponding Pdu clause is Asynchronous. The operation never fails, if it is important to know if the message was delivered, use call instead.

The message will be reduced to normal form (rnf) in the caller process.

call :: forall result destination protocol r q. (HasProcesses r q, TangiblePdu destination (Synchronous result), TangiblePdu protocol (Synchronous result), Tangible result, Embeds destination protocol, HasCallStack) => Endpoint destination -> Pdu protocol (Synchronous result) -> Eff r result Source #

Send a request Pdu and wait for the server to return a result value.

The type signature enforces that the corresponding Pdu clause is Synchronous.

Always prefer callWithTimeout over call

callWithTimeout :: forall result destination protocol r q. (HasProcesses r q, TangiblePdu destination (Synchronous result), TangiblePdu protocol (Synchronous result), Tangible result, Member Logs r, HasCallStack, Embeds destination protocol) => Endpoint destination -> Pdu protocol (Synchronous result) -> Timeout -> Eff r result Source #

Send an request Pdu and wait for the server to return a result value.

The type signature enforces that the corresponding Pdu clause is Synchronous.

If the server that was called dies, this function interrupts the process with ProcessDown. If the server takes longer to reply than the given timeout, this function interrupts the process with TimeoutInterrupt.

Always prefer this function over call

Since: 0.22.0

runEndpointReader :: HasCallStack => Endpoint o -> Eff (EndpointReader o ': r) a -> Eff r a Source #

Run a reader effect that contains the one server handling a specific Pdu instance.

askEndpoint :: Member (EndpointReader o) e => Eff e (Endpoint o) Source #

Get the Endpoint registered with runEndpointReader.

callEndpointReader :: forall reply o r q. (HasEndpointReader o r, HasCallStack, Tangible reply, TangiblePdu o (Synchronous reply), HasProcesses r q, Embeds o o) => Pdu o (Synchronous reply) -> Eff r reply Source #

Like call but take the Endpoint from the reader provided by runEndpointReader.

When working with an embedded Pdu use callSingleton.

castEndpointReader :: forall o r q. (HasEndpointReader o r, HasProcesses r q, Tangible (Pdu o Asynchronous), HasCallStack, HasPdu o, Embeds o o) => Pdu o Asynchronous -> Eff r () Source #

Like cast but take the Endpoint from the reader provided by runEndpointReader.

When working with an embedded Pdu use castSingleton.

callSingleton :: forall outer inner reply q e. (HasCallStack, Member (EndpointReader outer) e, Embeds outer inner, Embeds outer outer, HasProcesses e q, TangiblePdu outer (Synchronous reply), TangiblePdu inner (Synchronous reply), Tangible reply) => Pdu inner (Synchronous reply) -> Eff e reply Source #

Like callEndpointReader, uses embedPdu to embed the value.

This function makes use of AmbigousTypes and TypeApplications.

When not working with an embedded Pdu use callEndpointReader.

Since: 0.25.1

castSingleton :: forall outer inner q e. (HasCallStack, Member (EndpointReader outer) e, Tangible (Pdu outer Asynchronous), HasProcesses e q, HasPdu outer, HasPdu inner, Embeds outer inner, Embeds outer outer) => Pdu inner Asynchronous -> Eff e () Source #

Like castEndpointReader, but uses embedPdu to embed the value.

This function makes use of AmbigousTypes and TypeApplications.

When not working with an embedded Pdu use castEndpointReader.

Since: 0.25.1

Protocol-Server Support Functions for building protocol servers

newtype ReplyTarget p r Source #

Target of a Call reply.

This combines a RequestOrigin with a Serializer for a Reply using Arg. There are to smart constructors for this type: replyTarget and embeddedReplyTarget.

Because of Arg the Eq and Ord instances are implemented via the RequestOrigin instances.

Since: 0.26.0

Constructors

MkReplyTarget (Arg (RequestOrigin p r) (Serializer (Reply p r))) 
Instances
Eq (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

Methods

(==) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(/=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

Ord (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

Methods

compare :: ReplyTarget p r -> ReplyTarget p r -> Ordering #

(<) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(<=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(>) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

(>=) :: ReplyTarget p r -> ReplyTarget p r -> Bool #

max :: ReplyTarget p r -> ReplyTarget p r -> ReplyTarget p r #

min :: ReplyTarget p r -> ReplyTarget p r -> ReplyTarget p r #

Show (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

Methods

showsPrec :: Int -> ReplyTarget p r -> ShowS #

show :: ReplyTarget p r -> String #

showList :: [ReplyTarget p r] -> ShowS #

NFData (ReplyTarget p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

Methods

rnf :: ReplyTarget p r -> () #

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

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

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

Generic (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

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

Methods

rnf :: RequestOrigin p r -> () #

type Rep (RequestOrigin proto reply) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

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

data Reply protocol reply where Source #

The wrapper around replies to Calls.

Since: 0.15.0

Constructors

Reply 

Fields

Instances
Show r => Show (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

Methods

showsPrec :: Int -> Reply p r -> ShowS #

show :: Reply p r -> String #

showList :: [Reply p r] -> ShowS #

NFData (Reply p r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

Methods

rnf :: Reply p r -> () #

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, NFData (Pdu protocol Asynchronous)) => Pdu protocol Asynchronous -> Request protocol 
Instances
Show (Request protocol) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Wrapper

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

Methods

rnf :: Request protocol -> () #

makeRequestOrigin :: (Typeable r, NFData r, HasProcesses e q0) => Eff e (RequestOrigin p r) Source #

Create a new, unique RequestOrigin value for the current process.

Since: 0.24.0

toEmbeddedOrigin :: forall outer inner reply. Embeds outer inner => RequestOrigin outer reply -> RequestOrigin inner reply Source #

Turn an RequestOrigin to an origin for an embedded request (See Embeds).

This is useful of a server delegates the calls and casts for an embedded protocol to functions, that require the Serializer and RequestOrigin in order to call sendReply.

See also embedReplySerializer.

Since: 0.24.3

embedRequestOrigin :: forall outer inner reply. Embeds outer inner => RequestOrigin inner reply -> RequestOrigin outer reply Source #

Turn an embedded RequestOrigin to a RequestOrigin for the bigger request.

This is the inverse of toEmbeddedOrigin.

This function is strict in all parameters.

Since: 0.24.2

embedReplySerializer :: forall outer inner reply. Embeds outer inner => Serializer (Reply outer reply) -> Serializer (Reply inner reply) Source #

Turn a Serializer for a Pdu instance that contains embedded Pdu values into a Reply Serializer for the embedded Pdu.

This is useful of a server delegates the calls and casts for an embedded protocol to functions, that require the Serializer and RequestOrigin in order to call sendReply.

See also toEmbeddedOrigin.

Since: 0.24.2

sendReply :: (HasProcesses eff q, Tangible reply, Typeable protocol) => ReplyTarget protocol reply -> reply -> Eff eff () Source #

Answer a Call by sending the reply value to the client process.

The ProcessId, the RequestOrigin and the Reply Serializer are stored in the ReplyTarget.

Since: 0.25.1

replyTarget :: Serializer (Reply p reply) -> RequestOrigin p reply -> ReplyTarget p reply Source #

Smart constructor for a ReplyTarget.

To build a ReplyTarget for an Embeds instance use embeddedReplyTarget.

Since: 0.26.0

replyTargetOrigin :: Lens' (ReplyTarget p reply) (RequestOrigin p reply) Source #

A simple Lens for the RequestOrigin of a ReplyTarget.

Since: 0.26.0

replyTargetSerializer :: Lens' (ReplyTarget p reply) (Serializer (Reply p reply)) Source #

A simple Lens for the Reply Serializer of a ReplyTarget.

Since: 0.26.0

embeddedReplyTarget :: Embeds outer inner => Serializer (Reply outer reply) -> RequestOrigin outer reply -> ReplyTarget inner reply Source #

Smart constructor for an embedded ReplyTarget.

This combines replyTarget and toEmbeddedReplyTarget.

Since: 0.26.0

toEmbeddedReplyTarget :: Embeds outer inner => ReplyTarget outer reply -> ReplyTarget inner reply Source #

Convert a ReplyTarget to be usable for embedded replies.

This combines a toEmbeddedOrigin with embedReplySerializer to produce a ReplyTarget that can be passed to functions defined soley on an embedded protocol.

Since: 0.26.0

Observer Functions for Events and Event Listener

data family Pdu protocol (reply :: Synchronicity) Source #

The protocol data unit type for the given protocol.

Instances
(Show (Pdu a1 r), Show (Pdu a2 r)) => Show (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2) r -> ShowS #

show :: Pdu (a1, a2) r -> String #

showList :: [Pdu (a1, a2) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r)) => Show (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3) r -> ShowS #

show :: Pdu (a1, a2, a3) r -> String #

showList :: [Pdu (a1, a2, a3) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r)) => Show (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4) r -> ShowS #

show :: Pdu (a1, a2, a3, a4) r -> String #

showList :: [Pdu (a1, a2, a3, a4) r] -> ShowS #

(Show (Pdu a1 r), Show (Pdu a2 r), Show (Pdu a3 r), Show (Pdu a4 r), Show (Pdu a5 r)) => Show (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

showsPrec :: Int -> Pdu (a1, a2, a3, a4, a5) r -> ShowS #

show :: Pdu (a1, a2, a3, a4, a5) r -> String #

showList :: [Pdu (a1, a2, a3, a4, a5) r] -> ShowS #

Typeable event => Show (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (ObserverRegistry event) r -> ShowS #

show :: Pdu (ObserverRegistry event) r -> String #

showList :: [Pdu (ObserverRegistry event) r] -> ShowS #

Show event => Show (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer event) r -> ShowS #

show :: Pdu (Observer event) r -> String #

showList :: [Pdu (Observer event) r] -> ShowS #

(Typeable p, Show (ChildId p)) => Show (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

showsPrec :: Int -> Pdu (Broker p) r -> ShowS #

show :: Pdu (Broker p) r -> String #

showList :: [Pdu (Broker p) r] -> ShowS #

(Show (ChildId child), Typeable child, Typeable (ServerPdu child)) => Show (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

showsPrec :: Int -> Pdu (Watchdog child) r -> ShowS #

show :: Pdu (Watchdog child) r -> String #

showList :: [Pdu (Watchdog child) r] -> ShowS #

(NFData (Pdu a1 r), NFData (Pdu a2 r)) => NFData (Pdu (a1, a2) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r)) => NFData (Pdu (a1, a2, a3) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3) r -> () #

(NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r)) => NFData (Pdu (a1, a2, a3, a4) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4) r -> () #

(Typeable r, NFData (Pdu a1 r), NFData (Pdu a2 r), NFData (Pdu a3 r), NFData (Pdu a4 r), NFData (Pdu a5 r)) => NFData (Pdu (a1, a2, a3, a4, a5) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

rnf :: Pdu (a1, a2, a3, a4, a5) r -> () #

NFData (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry event) r -> () #

NFData event => NFData (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer event) r -> () #

NFData (ChildId p) => NFData (Pdu (Broker p) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

rnf :: Pdu (Broker p) r -> () #

NFData (ChildId child) => NFData (Pdu (Watchdog child) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

rnf :: Pdu (Watchdog child) r -> () #

data Pdu (ObserverRegistry event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Broker p) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

data Pdu (Broker p) r where
data Pdu (Watchdog child) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

data Pdu (Watchdog child) r where
type ToPretty (Pdu x y :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

type ToPretty (Pdu x y :: Type) = PrettySurrounded (PutStr "<") (PutStr ">") (("protocol" <:> ToPretty x) <+> ToPretty y)
data Pdu (a1, a2) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) r
data Pdu (Observer event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer event) r where
data Pdu (a1, a2, a3) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3) r
data Pdu (a1, a2, a3, a4) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4) r
data Pdu (a1, a2, a3, a4, a5) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2, a3, a4, a5) r

type ObserverRegistryState event = State (ObserverRegistry event) Source #

Alias for the effect that contains the observers managed by evalObserverRegistryState

data ObserverRegistry (event :: Type) Source #

A protocol for managing Observers, encompassing registration and de-registration of Observers.

Since: 0.28.0

Instances
Tangible event => HasPdu (ObserverRegistry event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (ObserverRegistry event) :: [Type] Source #

data Pdu (ObserverRegistry event) reply :: Type Source #

Typeable p => HasPduPrism (Broker p) (ObserverRegistry (ChildEvent p)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Broker

Methods

embeddedPdu :: Prism' (Pdu (Broker p) result) (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

embedPdu :: Pdu (ObserverRegistry (ChildEvent p)) result -> Pdu (Broker p) result Source #

fromPdu :: Pdu (Broker p) result -> Maybe (Pdu (ObserverRegistry (ChildEvent p)) result) Source #

Typeable event => Show (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (ObserverRegistry event) r -> ShowS #

show :: Pdu (ObserverRegistry event) r -> String #

showList :: [Pdu (ObserverRegistry event) r] -> ShowS #

NFData (Pdu (ObserverRegistry event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (ObserverRegistry event) r -> () #

type EmbeddedPduList (ObserverRegistry event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type EmbeddedPduList (ObserverRegistry event) = ([] :: [Type])
data Pdu (ObserverRegistry event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry event :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry event :: Type) = PrettyParens ("observer registry" <:> ToPretty event)

type CanObserve eventSink event = (Tangible event, Embeds eventSink (Observer event), HasPdu eventSink) Source #

Convenience type alias.

Since: 0.28.0

type IsObservable eventSource event = (Tangible event, Embeds eventSource (ObserverRegistry event), HasPdu eventSource) Source #

Convenience type alias.

Since: 0.28.0

data ObservationSink event Source #

The Information necessary to wrap an Observed event to a process specific message, e.g. the embedded Observer Pdu instance, and the MonitorReference of the destination process.

Since: 0.28.0

Instances
Generic (ObservationSink event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type Rep (ObservationSink event) :: Type -> Type #

Methods

from :: ObservationSink event -> Rep (ObservationSink event) x #

to :: Rep (ObservationSink event) x -> ObservationSink event #

NFData (ObservationSink event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: ObservationSink event -> () #

type Rep (ObservationSink event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type Rep (ObservationSink event) = D1 (MetaData "ObservationSink" "Control.Eff.Concurrent.Protocol.Observer" "extensible-effects-concurrent-0.32.0-GimAdtHOovq4dulPgeQPe9" False) (C1 (MetaCons "MkObservationSink" PrefixI True) (S1 (MetaSel (Just "_observerSerializer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Serializer (Pdu (Observer event) Asynchronous))) :*: S1 (MetaSel (Just "_observerMonitorReference") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 MonitorReference)))

newtype Observer event Source #

A protocol to communicate Observed events from a sources to many sinks.

A sink is any process that serves a protocol with a Pdu instance that embeds the Observer Pdu via an HasPduPrism instance.

This type has dual use, for one it serves as type-index for Pdu, i.e. HasPdu respectively, and secondly it contains an ObservationSink and a MonitorReference.

The ObservationSink is used to serialize and send the Observed events, while the ProcessId serves as key for internal maps.

Since: 0.28.0

Constructors

MkObserver (Arg ProcessId (ObservationSink event)) 
Instances
Typeable child => HasPduPrism (Watchdog child) (Observer (ChildEvent child)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Watchdog

Methods

embeddedPdu :: Prism' (Pdu (Watchdog child) result) (Pdu (Observer (ChildEvent child)) result) Source #

embedPdu :: Pdu (Observer (ChildEvent child)) result -> Pdu (Watchdog child) result Source #

fromPdu :: Pdu (Watchdog child) result -> Maybe (Pdu (Observer (ChildEvent child)) result) Source #

Eq (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

(==) :: Observer event -> Observer event -> Bool #

(/=) :: Observer event -> Observer event -> Bool #

Ord (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

compare :: Observer event -> Observer event -> Ordering #

(<) :: Observer event -> Observer event -> Bool #

(<=) :: Observer event -> Observer event -> Bool #

(>) :: Observer event -> Observer event -> Bool #

(>=) :: Observer event -> Observer event -> Bool #

max :: Observer event -> Observer event -> Observer event #

min :: Observer event -> Observer event -> Observer event #

Show event => Show (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Pdu (Observer event) r -> ShowS #

show :: Pdu (Observer event) r -> String #

showList :: [Pdu (Observer event) r] -> ShowS #

Typeable event => Show (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

showsPrec :: Int -> Observer event -> ShowS #

show :: Observer event -> String #

showList :: [Observer event] -> ShowS #

NFData event => NFData (Pdu (Observer event) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer event) r -> () #

NFData (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observer event -> () #

Tangible event => HasPdu (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Associated Types

type EmbeddedPduList (Observer event) :: [Type] Source #

data Pdu (Observer event) reply :: Type Source #

type ToPretty (Observer event :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (Observer event :: Type) = PrettyParens ("observing" <:> ToPretty event)
type EmbeddedPduList (Observer event) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type EmbeddedPduList (Observer event) = ([] :: [Type])
data Pdu (Observer event) r Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer event) r where

registerObserver :: forall event eventSink eventSource r q. (HasCallStack, HasProcesses r q, IsObservable eventSource event, Tangible (Pdu eventSource Asynchronous), Tangible (Pdu eventSink Asynchronous), CanObserve eventSink event) => Endpoint eventSource -> Endpoint eventSink -> Eff r () Source #

And an Observer to the set of recipients for all observations reported by observerRegistryNotify. Note that the observerRegistry are keyed by the observing process, i.e. a previous entry for the process contained in the Observer is overwritten. If you want multiple entries for a single process, just combine several filter functions.

Since: 0.16.0

forgetObserver :: forall event eventSink eventSource r q. (HasProcesses r q, HasCallStack, Tangible (Pdu eventSource Asynchronous), Tangible (Pdu eventSink Asynchronous), IsObservable eventSource event, CanObserve eventSink event) => Endpoint eventSource -> Endpoint eventSink -> Eff r () Source #

Send the ForgetObserver message

Since: 0.16.0

forgetObserverUnsafe :: forall event eventSource r q. (HasProcesses r q, HasCallStack, Tangible (Pdu eventSource Asynchronous), IsObservable eventSource event) => Endpoint eventSource -> ProcessId -> Eff r () Source #

Send the ForgetObserver message, use a raw ProcessId as parameter.

Since: 0.28.0

observerRegistryHandlePdu :: forall event q r. (HasCallStack, Typeable event, HasProcesses r q, Member (ObserverRegistryState event) r, Member Logs r) => Pdu (ObserverRegistry event) Asynchronous -> Eff r () Source #

Provide the implementation for the ObserverRegistry Protocol, this handled RegisterObserver and ForgetObserver messages. It also adds the ObserverRegistryState constraint to the effect list.

Since: 0.28.0

observerRegistryRemoveProcess :: forall event q r. (HasCallStack, Typeable event, HasProcesses r q, Member (ObserverRegistryState event) r, Member Logs r) => ProcessId -> Eff r Bool Source #

Remove the entry in the ObserverRegistry for the ProcessId and return True if there was an entry, False otherwise.

Since: 0.28.0

evalObserverRegistryState :: HasCallStack => Eff (ObserverRegistryState event ': r) a -> Eff r a Source #

Keep track of registered Observers.

Handle the ObserverRegistryState effect, i.e. run evalState on an emptyObserverRegistry.

Since: 0.28.0

observerRegistryNotify :: forall event r q. (HasProcesses r q, Member (ObserverRegistryState event) r, Tangible event, HasCallStack) => event -> Eff r () Source #

Report an observation to all observers. The process needs to evalObserverRegistryState and to observerRegistryHandlePdu.

Since: 0.28.0

Utilities

FilteredLogging Effect

Log Writer

Asynchronous

Console

File

UDP

Debug.Trace

Generic IO

Unix Domain Socket

Preventing Space Leaks