extensible-effects-concurrent-0.21.1: 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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" 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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" 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 ': ConsProcess e Source #

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

type InterruptReason = ExitReason Recoverable Source #

ExitReasons which are recoverable are interrupts.

data ExitReason (t :: ExitRecovery) where Source #

A sum-type with reasons for why a process exists the scheduling loop, this includes errors, that can occur when scheduling messages.

Constructors

ProcessFinished :: ExitReason 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

ProcessNotRunning :: ProcessId -> ExitReason Recoverable

A process that should be running was not running.

LinkedProcessCrashed :: ProcessId -> ExitReason Recoverable

A linked process is down

ProcessError :: String -> ExitReason Recoverable

An exit reason that has an error message but isn't Recoverable.

ExitNormally :: ExitReason NoRecovery

A process function returned or exited without any error.

NotRecovered :: ExitReason Recoverable -> ExitReason NoRecovery

An unhandled Recoverable allows NoRecovery.

UnexpectedException :: String -> String -> ExitReason NoRecovery

An unexpected runtime exception was thrown, i.e. an exception derived from SomeException

Killed :: ExitReason NoRecovery

A process was cancelled (e.g. killed, in cancel)

Instances
Eq (ExitReason x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

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

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

Ord (ExitReason x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show (ExitReason x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Exception (ExitReason Recoverable) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Exception (ExitReason NoRecovery) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData (ExitReason x) Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ExitReason x -> () #

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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" 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 ExitReason 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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" 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

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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" 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 "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)))))

type ConsProcess r = Process r ': r Source #

Cons Process onto a list of effects.

data SchedulerProxy :: [Type -> Type] -> Type where Source #

Every function for Process things needs such a proxy value for the low-level effect list, i.e. the effects identified by r in Process r : r, this might be dependent on the scheduler implementation.

Constructors

SchedulerProxy :: SchedulerProxy q

Tell the type checker what effects we have below Process

SP :: SchedulerProxy q

Like SchedulerProxy but shorter

Scheduler :: SchedulerProxy q

Like SP but different

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 :: InterruptReason -> ResumeProcess v

The current operation of the process was interrupted with a ExitReason. 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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" False) (C1 (MetaCons "Interrupted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InterruptReason)) :+: 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.21.1-9Yk6EWYMSLLHGr6bV3y5GS" False) (C1 (MetaCons "Interrupted" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InterruptReason)) :+: C1 (MetaCons "ResumeWith" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

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 [Dynamic])

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 :: 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 :: Eff (Process r ': r) () -> Process r (ResumeProcess ProcessId)

Start a new process, and Link to it .

Since: 0.12.0

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

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

Shutdown :: ExitReason NoRecovery -> Process r a

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

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

Raise an error, that can be handled.

SendInterrupt :: ProcessId -> InterruptReason -> 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 -> Dynamic -> 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 ExitReason LinkedProcessCrashed.

Since: 0.12.0

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

Unlink the calling process from the other process.

Since: 0.12.0

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 #

selectMessage :: (NFData t, Typeable t) => MessageSelector t Source #

Create a message selector for a value that can be obtained by fromDynamic. It will also force the result.

Since: 0.9.1

selectMessageLazy :: Typeable t => MessageSelector t Source #

Create a message selector for a value that can be obtained by fromDynamic. It will also force the result.

Since: 0.9.1

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

Create a message selector from a predicate. It will force the result.

Since: 0.9.1

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

Create a message selector from a predicate. It will force the result.

Since: 0.9.1

selectMessageWith :: (Typeable a, NFData b) => (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). It will force the result.

Since: 0.9.1

selectMessageWithLazy :: 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). It will force the result.

Since: 0.9.1

selectDynamicMessage :: NFData a => (Dynamic -> Maybe a) -> MessageSelector a Source #

Create a message selector. It will force the result.

Since: 0.9.1

selectDynamicMessageLazy :: (Dynamic -> Maybe a) -> MessageSelector a Source #

Create a message selector.

Since: 0.9.1

selectAnyMessageLazy :: MessageSelector Dynamic Source #

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

Since: 0.9.1

selectMessageProxy :: forall proxy t. (NFData t, Typeable t) => proxy t -> MessageSelector t Source #

Create a message selector for a value that can be obtained by fromDynamic with a proxy argument. It will also force the result.

Since: 0.9.1

selectMessageProxyLazy :: forall proxy t. Typeable t => proxy t -> MessageSelector t Source #

Create a message selector for a value that can be obtained by fromDynamic with a proxy argument. It will also force the result.

Since: 0.9.1

isBecauseDown :: Maybe ProcessId -> ExitReason r -> Bool Source #

A predicate for linked process crashes.

provideInterruptsShutdown :: forall e a. Eff (InterruptableProcess e) a -> Eff (ConsProcess e) a Source #

Handle all InterruptReasons of an InterruptableProcess by wrapping them up in NotRecovered and then do a process Shutdown.

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

Handle InterruptReasons 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 InterruptReason a) Source #

Like handleInterrupts, but instead of passing the InterruptReason 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 InterruptReasons 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 InterruptReason a) Source #

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

isCrash :: ExitReason x -> Bool Source #

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

isRecoverable :: ExitReason x -> Bool Source #

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

toCrashReason :: ExitReason x -> Maybe Text Source #

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

logCrash :: ExitReason -> 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) => ExitReason x -> Eff e () Source #

Log the ExitReasons

executeAndResume :: forall q r v. (SetMember Process (Process q) r, HasCallStack) => Process q (ResumeProcess v) -> Eff r (Either (ExitReason 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) => ProcessId -> o -> Eff r () Source #

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

sendAnyMessage :: forall r q. (SetMember Process (Process q) r, HasCallStack, Member Interrupts r) => ProcessId -> Dynamic -> 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 -> ExitReason 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 -> InterruptReason -> 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) => 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 InterruptReason wrapped in NotRecovered. For specific use cases it might be better to use spawnRaw.

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

Like spawn but return ().

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

receiveAnyMessage :: forall r q. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r) => Eff r Dynamic 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, 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 [Dynamic] 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 InterruptReason 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 ExitReason, 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 InterruptReason Dynamic -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

receiveLoop :: forall r q a endOfLoopResult. (SetMember Process (Process q) r, HasCallStack, Typeable a) => (Either InterruptReason a -> Eff r (Maybe endOfLoopResult)) -> Eff r endOfLoopResult Source #

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

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

Make an InterruptReason 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 ExitReason 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) => ExitReason NoRecovery -> Eff r a Source #

Exit the process with a ExitReason.

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.

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

Data Types and Functions for APIs (aka Protocols)

newtype Server api Source #

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

Constructors

Server 
Instances
Eq (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

(==) :: Server api -> Server api -> Bool #

(/=) :: Server api -> Server api -> Bool #

Ord (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

compare :: Server api -> Server api -> Ordering #

(<) :: Server api -> Server api -> Bool #

(<=) :: Server api -> Server api -> Bool #

(>) :: Server api -> Server api -> Bool #

(>=) :: Server api -> Server api -> Bool #

max :: Server api -> Server api -> Server api #

min :: Server api -> Server api -> Server api #

Typeable api => Show (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

showsPrec :: Int -> Server api -> ShowS #

show :: Server api -> String #

showList :: [Server api] -> ShowS #

data Synchronicity Source #

The (promoted) constructors of this type specify (at the type level) the reply behavior of a specific constructor of an Api 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

data family Api (api :: Type) (reply :: Synchronicity) Source #

This data family defines an API, a communication interface description between at least two processes. The processes act as servers or client(s) regarding a specific instance of this type.

The first parameter is usually a user defined phantom type that identifies the Api instance.

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

Example:

data BookShop deriving Typeable

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

type BookId = Int
type RentalId = Int
type RentalError = String
Instances
data Api (Observer o) r Source #

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

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (Observer o) r where
data Api (ObserverRegistry o) r Source #

Api 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.Api.Observer

data Api (ObserverRegistry o) r where

fromServer :: forall api api. Iso (Server api) (Server api) ProcessId ProcessId Source #

proxyAsServer :: proxy api -> ProcessId -> Server api Source #

Tag a ProcessId with an Api type index to mark it a Server process handling that API

asServer :: forall api. ProcessId -> Server api Source #

Tag a ProcessId with an Api type index to mark it a Server process handling that API

Client Functions for Consuming APIs

type ServerReader o = Reader (Server o) Source #

The reader effect for ProcessIds for Apis, see registerServer

type ServesApi o r q = (Typeable o, SetMember Process (Process q) r, Member (ServerReader o) r) Source #

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

cast :: forall r q o. (HasCallStack, SetMember Process (Process q) r, Member Interrupts r, Typeable o, Typeable (Api o Asynchronous)) => Server o -> Api o Asynchronous -> Eff r () Source #

Send an Api request that has no return value and return as fast as possible. The type signature enforces that the corresponding Api clause is Asynchronous. The operation never fails, if it is important to know if the message was delivered, use call instead.

call :: forall result api r q. (SetMember Process (Process q) r, Member Interrupts r, Typeable api, Typeable (Api api (Synchronous result)), Typeable result, HasCallStack, NFData result, Show result) => Server api -> Api api (Synchronous result) -> Eff r result Source #

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

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

registerServer :: HasCallStack => Server o -> Eff (ServerReader o ': r) a -> Eff r a Source #

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

whereIsServer :: Member (ServerReader o) e => Eff e (Server o) Source #

Get the Server registered with registerServer.

callRegistered :: (Typeable reply, ServesApi o r q, HasCallStack, NFData reply, Show reply, Member Interrupts r) => Api o (Synchronous reply) -> Eff r reply Source #

Like call but take the Server from the reader provided by registerServer.

castRegistered :: (Typeable o, ServesApi o r q, HasCallStack, Member Interrupts r) => Api o Asynchronous -> Eff r () Source #

Like cast but take the Server from the reader provided by registerServer.

Server Functions for Providing APIs

data InterruptCallback eff where Source #

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

Since: 0.13.2

Instances
Default (InterruptCallback eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Methods

def :: InterruptCallback eff #

class ToServerPids (t :: k) where Source #

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

Since: 0.13.2

Associated Types

type ServerPids t Source #

Methods

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

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

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type ServerPids api1 :: Type Source #

Methods

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

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

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

type ServerPids [] :: Type Source #

Methods

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

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

Defined in Control.Eff.Concurrent.Api.Server

Associated Types

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

Methods

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

data MessageCallback api eff where Source #

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

The return value if the handler function is a CallbackResult.

Since: 0.13.2

Constructors

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

Defined in Control.Eff.Concurrent.Api.Server

Methods

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

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

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

Monoid (MessageCallback api eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Methods

mempty :: MessageCallback api eff #

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

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

Default (MessageCallback api eff) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Server

Methods

def :: MessageCallback api eff #

data CallbackResult where Source #

A command to the server loop started by apiServerLoop. Typically returned by a MessageCallback to indicate if the server should continue or stop.

Since: 0.13.2

Constructors

AwaitNext :: CallbackResult

Tell the server to keep the server loop running

StopServer :: InterruptReason -> CallbackResult

Tell the server to exit, this will cause apiServerLoop to stop handling requests without exiting the process.

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

Serve an Api in a newly spawned process.

Since: 0.13.2

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

Serve an Api in a newly spawned -and linked - process.

Since: 0.14.2

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

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

Since: 0.13.2

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

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

Since: 0.13.2

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

Server an Api in a newly spawned process; The caller provides an effect handler for arbitrary effects used by the server callbacks. Links to the calling process like linkProcess would.

Since: 0.14.2

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

A smart constructor for MessageCallbacks

Since: 0.13.2

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

A smart constructor for MessageCallbacks

Since: 0.13.2

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

A smart constructor for MessageCallbacks

Since: 0.13.2

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

A smart constructor for MessageCallbacks

Since: 0.13.2

handleCalls :: forall api eff effScheduler. (HasCallStack, Typeable api, SetMember Process (Process effScheduler) eff, Member Interrupts eff) => (forall secret reply. (Typeable reply, Typeable (Api api (Synchronous reply))) => Api api (Synchronous reply) -> (Eff eff (Maybe reply, CallbackResult) -> secret) -> secret) -> MessageCallback api eff Source #

A smart constructor for MessageCallbacks

Example

Expand
handleCalls
  ( (RentBook bookId customerId) runCall ->
     runCall $ do
         rentalIdE <- rentBook bookId customerId
         case rentalIdE of
           -- on fail we just don't send a reply, let the caller run into
           -- timeout
           Left err -> return (Nothing, AwaitNext)
           Right rentalId -> return (Just rentalId, AwaitNext))

Since: 0.13.2

handleCastsAndCalls :: forall api eff effScheduler. (HasCallStack, Typeable api, Typeable (Api api Asynchronous), SetMember Process (Process effScheduler) eff, Member Interrupts eff) => (Api api Asynchronous -> Eff eff CallbackResult) -> (forall secret reply. (Typeable reply, Typeable (Api api (Synchronous reply))) => Api api (Synchronous reply) -> (Eff eff (Maybe reply, CallbackResult) -> secret) -> secret) -> MessageCallback api eff Source #

A smart constructor for MessageCallbacks

Since: 0.13.2

handleCallsDeferred :: forall api eff effScheduler. (HasCallStack, Typeable api, SetMember Process (Process effScheduler) eff, Member Interrupts eff) => (forall reply. (Typeable reply, Typeable (Api api (Synchronous reply))) => RequestOrigin (Api api (Synchronous reply)) -> Api api (Synchronous reply) -> Eff eff CallbackResult) -> MessageCallback api eff Source #

A variation of handleCalls that allows to defer a reply to a call.

Since: 0.14.2

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

A smart constructor for MessageCallbacks

Since: 0.13.2

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

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

handleCalls api1calls ^: handleCalls api2calls ^:

Since: 0.13.2

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

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

Since: 0.13.2

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

A fallbackHandler that drops the left-over messages.

Since: 0.13.2

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

A fallbackHandler that terminates if there are unhandled messages.

Since: 0.13.2

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

A fallbackHandler that drops the left-over messages.

Since: 0.13.2

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

A smart constructor for InterruptCallbacks

Since: 0.13.2

Encapsulate Apis Casts as well as Calls and their Replys

data RequestOrigin request Source #

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

Since: 0.15.0

Instances
Eq (RequestOrigin request) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Request

Methods

(==) :: RequestOrigin request -> RequestOrigin request -> Bool #

(/=) :: RequestOrigin request -> RequestOrigin request -> Bool #

Ord (RequestOrigin request) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Request

Methods

compare :: RequestOrigin request -> RequestOrigin request -> Ordering #

(<) :: RequestOrigin request -> RequestOrigin request -> Bool #

(<=) :: RequestOrigin request -> RequestOrigin request -> Bool #

(>) :: RequestOrigin request -> RequestOrigin request -> Bool #

(>=) :: RequestOrigin request -> RequestOrigin request -> Bool #

max :: RequestOrigin request -> RequestOrigin request -> RequestOrigin request #

min :: RequestOrigin request -> RequestOrigin request -> RequestOrigin request #

Show (RequestOrigin request) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Request

Methods

showsPrec :: Int -> RequestOrigin request -> ShowS #

show :: RequestOrigin request -> String #

showList :: [RequestOrigin request] -> ShowS #

Generic (RequestOrigin request) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Request

Associated Types

type Rep (RequestOrigin request) :: Type -> Type #

Methods

from :: RequestOrigin request -> Rep (RequestOrigin request) x #

to :: Rep (RequestOrigin request) x -> RequestOrigin request #

NFData (RequestOrigin request) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Request

Methods

rnf :: RequestOrigin request -> () #

type Rep (RequestOrigin request) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Request

type Rep (RequestOrigin request) = D1 (MetaData "RequestOrigin" "Control.Eff.Concurrent.Api.Request" "extensible-effects-concurrent-0.21.1-9Yk6EWYMSLLHGr6bV3y5GS" 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 request where Source #

The wrapper around replies to Calls.

Since: 0.15.0

Constructors

Reply :: (Typeable api, Typeable reply) => Proxy (Api api (Synchronous reply)) -> Int -> reply -> Reply (Api api (Synchronous reply)) 

data Request api where Source #

A wrapper sum type for calls and casts for the methods of an Api subtype

Since: 0.15.0

Constructors

Call :: forall api reply. (Typeable api, Typeable reply, Typeable (Api api (Synchronous reply))) => Int -> ProcessId -> Api api (Synchronous reply) -> Request api 
Cast :: forall api. (Typeable api, Typeable (Api api Asynchronous)) => Api api Asynchronous -> Request api 

mkRequestOrigin :: request -> ProcessId -> Int -> RequestOrigin request Source #

TODO remove

sendReply :: forall request reply api eff q. (SetMember Process (Process q) eff, Member Interrupts eff, Typeable api, ApiType request ~ api, ReplyType request ~ reply, request ~ Api api (Synchronous reply), Typeable reply) => RequestOrigin request -> reply -> Eff eff () Source #

Send a Reply to a Call.

Since: 0.15.0

Observer Functions for Events and Event Listener

data family Api (api :: Type) (reply :: Synchronicity) Source #

This data family defines an API, a communication interface description between at least two processes. The processes act as servers or client(s) regarding a specific instance of this type.

The first parameter is usually a user defined phantom type that identifies the Api instance.

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

Example:

data BookShop deriving Typeable

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

type BookId = Int
type RentalId = Int
type RentalError = String
Instances
data Api (Observer o) r Source #

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

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (Observer o) r where
data Api (ObserverRegistry o) r Source #

Api 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.Api.Observer

data Api (ObserverRegistry o) r where

type ObserverState o = State (Observers o) Source #

Alias for the effect that contains the observers managed by manageObservers

data ObserverRegistry o Source #

An Api for managing Observers, encompassing registration and de-registration of Observers.

Since: 0.16.0

Instances
data Api (ObserverRegistry o) r Source #

Api 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.Api.Observer

data Api (ObserverRegistry o) r where

data Observer o where Source #

Describes a process that observes another via Asynchronous Api 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 :: (Show (Server p), Typeable p, Typeable o) => (o -> Maybe (Api p Asynchronous)) -> Server p -> Observer o 
Instances
Eq (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Observer

Methods

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

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

Ord (Observer o) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.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.Api.Observer

Methods

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

show :: Observer o -> String #

showList :: [Observer o] -> ShowS #

data Api (Observer o) r Source #

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

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (Observer o) r where

registerObserver :: (SetMember Process (Process q) r, HasCallStack, Member Interrupts r, Typeable o) => Observer o -> Server (ObserverRegistry o) -> 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) => (o -> Eff r CallbackResult) -> MessageCallback (Observer o) r Source #

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

Since: 0.16.0

toObserver :: Typeable o => Server (Observer o) -> Observer o Source #

Use a Server as an Observer for handleObservations.

Since: 0.16.0

toObserverFor :: (Typeable a, Typeable o) => (o -> Api a Asynchronous) -> Server 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 Api 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) => MessageCallback (ObserverRegistry o) r Source #

Provide the implementation for the ObserverRegistry Api, 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

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

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. (Typeable o, Show o, Member Logs q, Lifted IO 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

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 (ExitReason 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.

Utilities

Logging Effect

Log Writer

Asynchronous

Console

File

UDP

Non-IO Log Message Capturing

Debug.Trace

Generic IO

Unix Domain Socket

Preventing Space Leaks