extensible-effects-concurrent-0.6.2: 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 (ConsProcess r) a 
-> m (Either String 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 exitNormally, exitWithError, raiseError 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: extensible-effects-concurrent-0.4.0.0

schedulePure :: Eff (ConsProcess '[]) a -> Either String a Source #

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

Since: extensible-effects-concurrent-0.3.0.2

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

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

Since: extensible-effects-concurrent-0.4.0.0

scheduleMonadIOEff :: MonadIO (Eff r) => Eff (ConsProcess r) a -> Eff r (Either String a) Source #

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

Since: extensible-effects-concurrent-0.3.0.2

scheduleIOWithLogging :: (NFData l, MonadIO m) => (l -> m ()) -> Eff (ConsProcess '[Logs l, Lift m]) a -> m (Either String 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 == run . captureLogs . schedule (return ())

Since: extensible-effects-concurrent-0.4.0.0

defaultMain :: HasCallStack => Eff '[Process '[Logs LogMessage, Lift IO], Logs LogMessage, Lift IO] () -> IO () Source #

Execute a Process using schedule on top of Lift IO and Logs String effects.

type LoggingAndIo = '[Logs LogMessage, Lift IO] Source #

The concrete list of Effects for running this pure scheduler on IO and with string logging.