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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Process

Contents

Description

The message passing effect.

This module describes an abstract message passing effect, and a process effect, mimicking Erlang's process and message semantics.

Two scheduler implementations for the Process effect are provided:

Synopsis

Process Effect

Effect Type Handling

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) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

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

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

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

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

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

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

Methods

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

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

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

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

Process Info

newtype ProcessTitle Source #

A short title for a Process for logging purposes.

Since: 0.24.1

Constructors

MkProcessTitle 
Instances
Eq ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

IsString ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessTitle :: Type -> Type #

Semigroup ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Monoid ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessTitle -> () #

type Rep ProcessTitle Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

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

fromProcessTitle :: Lens' ProcessTitle Text Source #

An isomorphism lens for the ProcessTitle

Since: 0.24.1

newtype ProcessDetails Source #

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

Since: 0.24.1

Constructors

MkProcessDetails 
Instances
Eq ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Ord ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Show ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

IsString ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Generic ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Associated Types

type Rep ProcessDetails :: Type -> Type #

Semigroup ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Monoid ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

NFData ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

Methods

rnf :: ProcessDetails -> () #

type Rep ProcessDetails Source # 
Instance details

Defined in Control.Eff.Concurrent.Process

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

fromProcessDetails :: Lens' ProcessDetails Text Source #

An isomorphism lens for the ProcessDetails

Since: 0.24.1

Message Data

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

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

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 #

ProcessId Type

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

type SafeProcesses r = Process r ': r Source #

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

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.25.0-IFcNAKfATcZH0zT1MWbAEU" 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.25.0-IFcNAKfATcZH0zT1MWbAEU" 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))

Process State

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.25.0-IFcNAKfATcZH0zT1MWbAEU" 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)))))

Yielding

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.

Sending Messages

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.

Utilities

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

Generate a unique Int for the current process.

Receiving Messages

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

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.

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

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.

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.

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.

Selecting Messages to Receive

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

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

Process Life Cycle Management

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

Returns the ProcessId of the current process.

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

Spawning

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

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

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

Like spawn but return ().

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

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

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

Like spawnRaw but return ().

Process Exit or Interrupt Recoverable

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.

Links

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

Monitors

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

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

selectProcessDown :: MonitorReference -> MessageSelector ProcessDown Source #

A MessageSelector for the ProcessDown message of a specific process.

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

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.25.0-IFcNAKfATcZH0zT1MWbAEU" False) (C1 (MetaCons "MonitorReference" PrefixI True) (S1 (MetaSel (Just "monitorIndex") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "monitoredProcess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessId)))

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

Process Interrupt Recoverable Handling

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

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

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

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

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

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

Since: 0.13.2

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.

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.

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.

Process Operation Execution

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.

Exit Or Interrupt Recoverable Reasons

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) (Processes e)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

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

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

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Methods

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

Associated Types

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

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

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

Methods

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

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

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

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

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

Defined in Control.Eff.Concurrent.Protocol.EffectfulServer

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

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.25.0-IFcNAKfATcZH0zT1MWbAEU" False) (C1 (MetaCons "Recoverable" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoRecovery" PrefixI False) (U1 :: Type -> Type))

type Processes e = Interrupts ': SafeProcesses e Source #

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

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.25.0-IFcNAKfATcZH0zT1MWbAEU" False) (C1 (MetaCons "NormalExit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Crash" PrefixI False) (U1 :: Type -> Type))

isRecoverable :: Interrupt x -> Bool Source #

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

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

A predicate for linked process crashes.

isCrash :: Interrupt x -> Bool Source #

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

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