extensible-effects-concurrent-0.24.2: 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.

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.24.2-4i89KX4lrqK4F8mqMzm4qM" False) (C1 (MetaCons "ProcessDown" PrefixI True) (S1 (MetaSel (Just "downReference") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MonitorReference) :*: S1 (MetaSel (Just "downReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SomeExitReason)))

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.24.2-4i89KX4lrqK4F8mqMzm4qM" 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 InterruptableProcess e = Interrupts ': (Process e ': e) Source #

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

type ConsProcess r = Process r ': r Source #

Cons Process onto a list of effects.

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

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

ErrorInterrupt :: String -> Interrupt Recoverable

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

ExitNormally :: Interrupt NoRecovery

A process function returned or exited without any error.

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 :: Interrupt NoRecovery

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

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 tag => Show (Init (GenServer tag eLoop e) (InterruptableProcess e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

showsPrec :: Int -> Init (GenServer tag eLoop e) (InterruptableProcess e) -> ShowS #

show :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> String #

showList :: [Init (GenServer tag eLoop e) (InterruptableProcess e)] -> ShowS #

NFData (Init (GenServer tag eLoop e) (InterruptableProcess e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

rnf :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> () #

TangibleGenServer tag eLoop e => Server (GenServer tag eLoop e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

data Init (GenServer tag eLoop e) (InterruptableProcess e) :: Type Source #

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

type Effects (GenServer tag eLoop e) (InterruptableProcess e) :: [Type -> Type] Source #

data Init (GenServer tag eLoop e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type Effects (GenServer tag eLoop e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type Effects (GenServer tag eLoop e) (InterruptableProcess 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.24.2-4i89KX4lrqK4F8mqMzm4qM" 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.24.2-4i89KX4lrqK4F8mqMzm4qM" False) (C1 (MetaCons "Recoverable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoRecovery" PrefixI False) (U1 :: Type -> Type))

data ProcessState Source #

The state that a Process is currently in.

Constructors

ProcessBooting

The process has just been started but not scheduled yet.

ProcessIdle

The process yielded it's time slice

ProcessBusy

The process is busy with non-blocking

ProcessBusyUpdatingDetails

The process is busy with UpdateProcessDetails

ProcessBusySending

The process is busy with sending a message

ProcessBusySendingShutdown

The process is busy with killing

ProcessBusySendingInterrupt

The process is busy with killing

ProcessBusyReceiving

The process blocked by a receiveAnyMessage

ProcessBusyLinking

The process blocked by a linkProcess

ProcessBusyUnlinking

The process blocked by a unlinkProcess

ProcessBusyMonitoring

The process blocked by a monitor

ProcessBusyDemonitoring

The process blocked by a demonitor

ProcessInterrupted

The process was interrupted

ProcessShuttingDown

The process was shutdown or crashed

Instances
Enum ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Eq ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Read ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessState :: Type -> Type #

Default ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

def :: ProcessState #

NFData ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessState -> () #

type Rep ProcessState Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

type Rep ProcessState = D1 (MetaData "ProcessState" "Control.Eff.Concurrent.Process" "extensible-effects-concurrent-0.24.2-4i89KX4lrqK4F8mqMzm4qM" False) (((C1 (MetaCons "ProcessBooting" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProcessIdle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusy" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ProcessBusyUpdatingDetails" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusySending" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ProcessBusySendingShutdown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusySendingInterrupt" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "ProcessBusyReceiving" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProcessBusyLinking" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusyUnlinking" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ProcessBusyMonitoring" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessBusyDemonitoring" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ProcessInterrupted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProcessShuttingDown" 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.24.2-4i89KX4lrqK4F8mqMzm4qM" 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.24.2-4i89KX4lrqK4F8mqMzm4qM" 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 #

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

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

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.

Since: 0.12.0

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

Unlink the calling process from the other process.

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

Typeable tag => Show (Init (GenServer tag eLoop e) (InterruptableProcess e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

showsPrec :: Int -> Init (GenServer tag eLoop e) (InterruptableProcess e) -> ShowS #

show :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> String #

showList :: [Init (GenServer tag eLoop e) (InterruptableProcess e)] -> ShowS #

NFData (Init (GenServer tag eLoop e) (InterruptableProcess e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

rnf :: Init (GenServer tag eLoop e) (InterruptableProcess e) -> () #

TangibleGenServer tag eLoop e => Server (GenServer tag eLoop e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

data Init (GenServer tag eLoop e) (InterruptableProcess e) :: Type Source #

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

type Effects (GenServer tag eLoop e) (InterruptableProcess e) :: [Type -> Type] Source #

data Init (GenServer tag eLoop e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type Effects (GenServer tag eLoop e) (InterruptableProcess e) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

type Effects (GenServer tag eLoop e) (InterruptableProcess e) = eLoop

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 (InterruptableProcess e) a -> Eff (ConsProcess e) a Source #

Handle all Interrupts of an InterruptableProcess 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, Member Interrupts r, SetMember Process (Process q) r) => 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. (SetMember Process (Process q) r, 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. (SetMember Process (Process q) r, 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. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => 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. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => Eff r () Source #

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

sendMessage :: forall r q o. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, 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. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => ProcessId -> StrictDynamic -> Eff r () Source #

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

sendShutdown :: forall r q. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => 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. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => 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, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (InterruptableProcess 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, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (InterruptableProcess q) () -> Eff r () Source #

Like spawn but return ().

spawnLink :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (InterruptableProcess q) () -> Eff r ProcessId Source #

Start a new process, and immediately link to it.

Since: 0.12.0

spawnRaw :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (ConsProcess 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 ConsProcess effects. For non-library code spawn might be better suited.

spawnRaw_ :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessTitle -> Eff (ConsProcess q) () -> Eff r () Source #

Like spawnRaw but return ().

isProcessAlive :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r Bool Source #

Return True if the process is alive.

Since: 0.12.0

getProcessState :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => 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, SetMember Process (Process q) r, Member Interrupts r) => ProcessDetails -> Eff r () Source #

Replace the ProcessDetails of the process.

Since: 0.24.1

receiveAnyMessage :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Eff r StrictDynamic Source #

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

receiveSelectedMessage :: forall r q a. (HasCallStack, Show a, SetMember Process (Process q) r, Member Interrupts r) => 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, SetMember Process (Process q) r, Member Interrupts r) => 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, SetMember Process (Process q) r, Member Interrupts r) => 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. (SetMember Process (Process q) r, 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. (SetMember Process (Process q) r, 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. (SetMember Process (Process q) r, 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, SetMember Process (Process q) r) => Eff r ProcessId Source #

Returns the ProcessId of the current process.

makeReference :: (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Eff r Int Source #

Generate a unique Int for the current process.

monitor :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => 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, SetMember Process (Process q) r, Member Interrupts r) => MonitorReference -> Eff r () Source #

Remove a monitor created with monitor.

Since: 0.12.0

withMonitor :: (HasCallStack, Member Interrupts r, SetMember Process (Process q) r, Member Interrupts r) => 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, Member Interrupts r, SetMember Process (Process q) r, Member Interrupts r, 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.

Since: 0.12.0

linkProcess :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => 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.

Since: 0.12.0

unlinkProcess :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => ProcessId -> Eff r () Source #

Unlink the calling process from the other process.

Since: 0.12.0

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

Exit the process with a Interrupt.

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

Exit the process.

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

Exit the process with an error.

Scheduler Process Effect Handler

Concurrent Scheduler

type SchedulerIO = Reader SchedulerState ': LoggingAndIo Source #

The concrete list of Effects for this scheduler implementation.

type HasSchedulerIO r = (HasCallStack, Lifted IO r, SchedulerIO <:: r) Source #

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

type InterruptableProcEff = InterruptableProcess SchedulerIO Source #

The concrete list of the effects, that the Process uses

type ProcEff = ConsProcess SchedulerIO Source #

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

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

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

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

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

schedule :: HasCallStack => Eff InterruptableProcEff () -> 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 SchedulerIO effect for concurrent logging.

Single Threaded Scheduler

schedulePure :: Eff (InterruptableProcess '[Logs, LogWriterReader PureLogWriter]) a -> Either (Interrupt NoRecovery) a Source #

Like scheduleIO but pure. The yield effect is just return (). schedulePure == runIdentity . scheduleM (Identity . run) (return ())

Since: 0.3.0.2

defaultMainSingleThreaded :: HasCallStack => Eff (InterruptableProcess LoggingAndIo) () -> IO () Source #

Execute a Process using scheduleM on top of Lift IO and withLogging String effects.

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

data Timeout Source #

A number of micro seconds.

Since: 0.12.0

Instances
Enum Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Eq Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Methods

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

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

Integral Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Num Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Ord Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Real Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Show Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

NFData Timeout Source # 
Instance details

Defined in Control.Eff.Concurrent.Process.Timer

Methods

rnf :: Timeout -> () #

receiveAfter :: forall a r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r, 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. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r, Show 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

sendAfter :: forall r q message. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r, 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

startTimer :: forall r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => 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.

Since: 0.12.0

cancelTimer :: forall r q. (Lifted IO q, HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => TimerReference -> Eff r () Source #

Cancel a timer started with startTimer.

Since: 0.12.0

Data Types and Functions for APIs (aka Protocols)

newtype Endpoint protocol Source #

This is a tag-type that wraps around a ProcessId and holds an Pdu index type.

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"

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

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

This 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

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

type BookId = Int
type RentalId = Int
type RentalError = String
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 #

Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

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

show :: Pdu (Sup p) (Synchronous r) -> String #

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

Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

showList :: [Pdu (Observer o) 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 -> () #

(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 (ChildId p) => NFData (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

rnf :: Pdu (Sup p) (Synchronous r) -> () #

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

NFData o => NFData (Pdu (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) Asynchronous -> () #

data Pdu (Observer o) r Source #

A minimal Protocol for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Pdu message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) 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) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) x
data Pdu (Sup p) r Source #

The Pdu instance contains methods to start, stop and lookup a child process, as well as a diagnostic callback.

Since: 0.23.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data Pdu (Sup p) r where
data Pdu (ObserverRegistry o) r Source #

Protocol for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (ObserverRegistry o) r where
data Pdu (a1, a2, a3) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

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

Defined in Control.Eff.Concurrent.Protocol

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

Defined in Control.Eff.Concurrent.Protocol

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

class EmbedProtocol protocol embeddedProtocol where Source #

A class for Pdu instances that embed other Pdu. A Prism for the embedded Pdu is the center of this class

Laws: embeddedPdu = prism' embedPdu fromPdu

Since: 0.24.0

Minimal complete definition

Nothing

Methods

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

A Prism for the embedded Pdus.

embedPdu :: Pdu embeddedProtocol r -> Pdu protocol r Source #

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

fromPdu :: Pdu protocol r -> Maybe (Pdu embeddedProtocol r) Source #

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

Instances
EmbedProtocol a a Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

Methods

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

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

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

EmbedProtocol (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 r -> Pdu (a1, a2) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4, a5) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4, a5) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4, a5) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4, a5) r Source #

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

EmbedProtocol (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 r -> Pdu (a1, a2, a3, a4, a5) r Source #

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

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

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

Client Functions for Consuming APIs

type EndpointReader o = Reader (Endpoint o) Source #

The reader effect for ProcessIds for Pdus, see runEndpointReader

type ServesProtocol o r q = (Typeable o, SetMember Process (Process q) r, 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 o' o r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r, TangiblePdu o' Asynchronous, TangiblePdu o Asynchronous, EmbedProtocol o' o) => Endpoint o' -> Pdu o 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 protocol' protocol r q. (SetMember Process (Process q) r, Member Interrupts r, TangiblePdu protocol' (Synchronous result), TangiblePdu protocol (Synchronous result), EmbedProtocol protocol' protocol, Tangible result, HasCallStack) => Endpoint protocol' -> 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 protocol' protocol r q. (SetMember Process (Process q) r, Member Interrupts r, TangiblePdu protocol' (Synchronous result), TangiblePdu protocol (Synchronous result), EmbedProtocol protocol' protocol, Tangible result, Member Logs r, Lifted IO q, Lifted IO r, HasCallStack) => Endpoint protocol' -> 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. (ServesProtocol o r q, HasCallStack, Tangible reply, TangiblePdu o (Synchronous reply), Member Interrupts r) => Pdu o (Synchronous reply) -> Eff r reply Source #

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

castEndpointReader :: forall o r q. (ServesProtocol o r q, HasCallStack, Member Interrupts r, TangiblePdu o Asynchronous) => Pdu o Asynchronous -> Eff r () Source #

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

Observer Functions for Events and Event Listener

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

This 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

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

type BookId = Int
type RentalId = Int
type RentalError = String
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 #

Show (ChildId p) => Show (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

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

show :: Pdu (Sup p) (Synchronous r) -> String #

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

Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

showList :: [Pdu (Observer o) 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 -> () #

(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 (ChildId p) => NFData (Pdu (Sup p) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

Methods

rnf :: Pdu (Sup p) (Synchronous r) -> () #

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

NFData o => NFData (Pdu (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) Asynchronous -> () #

data Pdu (Observer o) r Source #

A minimal Protocol for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Pdu message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) 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) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

data Pdu (a1, a2) x
data Pdu (Sup p) r Source #

The Pdu instance contains methods to start, stop and lookup a child process, as well as a diagnostic callback.

Since: 0.23.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Supervisor

data Pdu (Sup p) r where
data Pdu (ObserverRegistry o) r Source #

Protocol for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (ObserverRegistry o) r where
data Pdu (a1, a2, a3) x Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol

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

Defined in Control.Eff.Concurrent.Protocol

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

Defined in Control.Eff.Concurrent.Protocol

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

type ObserverState o = State (Observers o) Source #

Alias for the effect that contains the observers managed by manageObservers

data Observers o Source #

Internal state for manageObservers

Instances
Eq (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

Ord (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Show (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

NFData o => NFData (Observers o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observers o -> () #

data ObserverRegistry o Source #

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

Since: 0.16.0

Instances
Show (Pdu (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (ObserverRegistry o :: Type) = PrettyParens ("observer registry" <:> ToPretty o)
data Pdu (ObserverRegistry o) r Source #

Protocol for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (ObserverRegistry o) r where

data Observer o where Source #

Describes a process that observes another via Asynchronous Pdu messages.

An observer consists of a filter and a process id. The filter converts an observation to a message understood by the observer process, and the ProcessId is used to send the message.

Since: 0.16.0

Constructors

Observer :: (Tangible o, TangiblePdu p Asynchronous, Tangible (Endpoint p), Typeable p) => (o -> Maybe (Pdu p Asynchronous)) -> Endpoint p -> Observer o 
Instances
Eq (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

Ord (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

compare :: Observer o -> Observer o -> Ordering #

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

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

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

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

max :: Observer o -> Observer o -> Observer o #

min :: Observer o -> Observer o -> Observer o #

Show (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

show :: Observer o -> String #

showList :: [Observer o] -> ShowS #

NFData o => NFData (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Observer o -> () #

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

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

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

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

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

NFData o => NFData (Pdu (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

Methods

rnf :: Pdu (Observer o) Asynchronous -> () #

data Pdu (Observer o) r Source #

A minimal Protocol for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Pdu message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

data Pdu (Observer o) r where
type ToPretty (Observer o :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.Observer

type ToPretty (Observer o :: Type) = PrettyParens ("observing" <:> ToPretty o)

registerObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, TangibleObserver o, EmbedProtocol x (ObserverRegistry o), TangiblePdu x Asynchronous) => Observer o -> Endpoint x -> Eff r () Source #

And an Observer to the set of recipients for all observations reported by observed. Note that the observers 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

handleObservations :: (HasCallStack, Typeable o, SetMember Process (Process q) r, NFData (Observer o)) => (o -> Eff r ()) -> Pdu (Observer o) Asynchronous -> Eff r () Source #

Based on the Pdu instance for Observer this simplified writing a callback handler for observations. In order to register to and ObserverRegistry use toObserver.

Since: 0.16.0

toObserverFor :: (TangibleObserver o, Typeable a, TangiblePdu a Asynchronous) => (o -> Pdu a Asynchronous) -> Endpoint a -> Observer o Source #

Create an Observer that conditionally accepts all observations of the given type and applies the given function to them; the function takes an observation and returns an Pdu cast that the observer server is compatible to.

Since: 0.16.0

handleObserverRegistration :: forall o q r. (HasCallStack, Typeable o, SetMember Process (Process q) r, Member (ObserverState o) r, Member Logs r) => Pdu (ObserverRegistry o) Asynchronous -> Eff r () Source #

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

Since: 0.16.0

manageObservers :: Eff (ObserverState o ': r) a -> Eff r a Source #

Keep track of registered Observers.

Handle the ObserverState introduced by handleObserverRegistration.

Since: 0.16.0

emptyObservers :: Observers o Source #

The empty ObserverState

Since: 0.24.0

observed :: forall o r q. (SetMember Process (Process q) r, Member (ObserverState o) r, Member Interrupts r, TangibleObserver o) => o -> Eff r () Source #

Report an observation to all observers. The process needs to manageObservers and to handleObserverRegistration.

Since: 0.16.0

Capture Observation in a FIFO Queue

data ObservationQueue a Source #

Contains a TBQueue capturing observations. See spawnLinkObservationQueueWriter, readObservationQueue.

readObservationQueue :: forall o r. (Member (ObservationQueueReader o) r, HasCallStack, MonadIO (Eff r), Typeable o, Member Logs r) => Eff r o Source #

Read queued observations captured and enqueued in the shared TBQueue by spawnLinkObservationQueueWriter. This blocks until something was captured or an interrupt or exceptions was thrown. For a non-blocking variant use tryReadObservationQueue or flushObservationQueue.

tryReadObservationQueue :: forall o r. (Member (ObservationQueueReader o) r, HasCallStack, MonadIO (Eff r), Typeable o, Member Logs r) => Eff r (Maybe o) Source #

Read queued observations captured and enqueued in the shared TBQueue by spawnLinkObservationQueueWriter. Return the oldest enqueued observation immediately or Nothing if the queue is empty. Use readObservationQueue to block until an observation is observed.

flushObservationQueue :: forall o r. (Member (ObservationQueueReader o) r, HasCallStack, MonadIO (Eff r), Typeable o, Member Logs r) => Eff r [o] Source #

Read at once all currently queued observations captured and enqueued in the shared TBQueue by spawnLinkObservationQueueWriter. This returns immediately all currently enqueued observations. For a blocking variant use readObservationQueue.

withObservationQueue :: forall o b e len. (HasCallStack, Typeable o, Show o, Member Logs e, Lifted IO e, Integral len, Member Interrupts e) => len -> Eff (ObservationQueueReader o ': e) b -> Eff e b Source #

Create a mutable queue for observations. Use spawnLinkObservationQueueWriter for a simple way to get a process that enqueues all observations.

Example

Expand
withObservationQueue 100 $ do
  q  <- ask @(ObservationQueueReader TestEvent)
  wq <- spawnLinkObservationQueueWriter q
  registerObserver wq testServer
  ...
  cast testServer DoSomething
  evt <- readObservationQueue @TestEvent
  ...

Since: 0.18.0

spawnLinkObservationQueueWriter :: forall o q h. (TangibleObserver o, TangiblePdu (Observer o) Asynchronous, Member Logs q, Lifted IO q, LogsTo h (InterruptableProcess q), HasCallStack) => ObservationQueue o -> Eff (InterruptableProcess q) (Observer o) Source #

Spawn a process that can be used as an Observer that enqueues the observations into an ObservationQueue. See withObservationQueue for an example.

The observations can be obtained by readObservationQueue. All observations are captured up to the queue size limit, such that the first message received will be first message returned by readObservationQueue.

Since: 0.18.0

Utilities

Logging Effect

Log Writer

Asynchronous

Console

File

UDP

Non-IO Log Message Capturing

Debug.Trace

Generic IO

Unix Domain Socket

Preventing Space Leaks