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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Process.SingleThreadedScheduler

Description

A coroutine based, single threaded scheduler for Processes.

Synopsis

Documentation

scheduleM Source #

Arguments

:: Monad m 
=> (forall b. Eff r b -> m b) 
-> m ()

An that performs a yield w.r.t. the underlying effect r. E.g. if Lift IO is present, this might be: @lift yield.

-> Eff (Processes r) a 
-> m (Either (Interrupt NoRecovery) a) 

Handle the Process effect, as well as all lower effects using an effect handler function.

Execute the main Process and all the other processes spawned by it in the current thread concurrently, using a co-routine based, round-robin scheduler. If a process exits with eg.g exitNormally or exitWithError or is killed by another process Left ... is returned. Otherwise, the result will be wrapped in a Right.

Every time a process _yields_ the effects are evaluated down to the a value of type m (Either String a).

If the evaluator function runs the action down e.g. IO this might improve memory consumption, for long running services, with processes that loop endlessly.

Since: 0.4.0.0

scheduleMonadIOEff :: MonadIO (Eff r) => Eff (Processes r) a -> Eff r (Either (Interrupt NoRecovery) a) Source #

Invoke scheduleM with lift yield as yield effect. scheduleMonadIOEff == scheduleM id (liftIO yield)

Since: 0.3.0.2

scheduleIOWithLogging :: HasCallStack => LogWriter -> Eff EffectsIo a -> IO (Either (Interrupt NoRecovery) a) Source #

Run processes that have the Logs and the Lift effects. The user must provide a log handler function.

Log messages are evaluated strict.

scheduleIOWithLogging == scheduleIO . withLogging

Since: 0.4.0.0

schedulePure :: Eff (Processes PureBaseEffects) a -> Either (Interrupt NoRecovery) a Source #

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

Since: 0.3.0.2

type PureEffects = Processes PureBaseEffects Source #

The effect list for Process effects in the single threaded pure scheduler.

See PureBaseEffects and Processes

Since: 0.25.0

type PureSafeEffects = SafeProcesses PureBaseEffects Source #

The effect list for Process effects in the single threaded pure scheduler. This is like SafeProcesses, no Interrupts are present.

See PureBaseEffects and SafeProcesses

Since: 0.25.0

type PureBaseEffects = '[Logs, LogWriterReader] Source #

The effect list for a pure, single threaded scheduler contains only Logs and the LogWriterReader for PureLogWriter.

Since: 0.25.0

type HasPureBaseEffects e = (HasCallStack, PureBaseEffects <:: e) Source #

Constraint for the existence of the underlying scheduler effects.

See PureBaseEffects

Since: 0.25.0

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

Execute a Process using scheduleM on top of Lift IO. All logging is written to the console using consoleLogWriter.

To use another LogWriter use defaultMainWithLogWriter instead.

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

Execute a Process using scheduleM on top of Lift IO. All logging is written using the given LogWriter.

Since: 0.25.0

scheduleIO :: MonadIO m => (forall b. Eff r b -> Eff '[Lift m] b) -> Eff (Processes r) a -> m (Either (Interrupt NoRecovery) a) Source #

Invoke scheduleM with lift yield as yield effect. scheduleIO runEff == scheduleM (runLift . runEff) (liftIO yield)

Since: 0.4.0.0

type EffectsIo = Processes BaseEffectsIo Source #

The effect list for Process effects in the single threaded scheduler.

See BaseEffectsIo

Since: 0.25.0

type SafeEffectsIo = SafeProcesses BaseEffectsIo Source #

The effect list for Process effects in the single threaded scheduler. This is like SafeProcesses, no Interrupts are present.

See BaseEffectsIo.

Since: 0.25.0

type BaseEffectsIo = LoggingAndIo Source #

The effect list for the underlying scheduler.

See LoggingAndIo

Since: 0.25.0

type HasBaseEffectsIo e = (HasCallStack, Lifted IO e, LoggingAndIo <:: e) Source #

Constraint for the existence of the underlying scheduler effects.

Since: 0.25.0