| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Eff.Concurrent.Process.SingleThreadedScheduler
Description
A coroutine based, single threaded scheduler for Processes.
Synopsis
- scheduleM :: forall m r a. Monad m => (forall b. Eff r b -> m b) -> m () -> Eff (InterruptableProcess r) a -> m (Either (Interrupt NoRecovery) a)
- schedulePure :: Eff (InterruptableProcess '[Logs, LogWriterReader PureLogWriter]) a -> Either (Interrupt NoRecovery) a
- scheduleIO :: MonadIO m => (forall b. Eff r b -> Eff '[Lift m] b) -> Eff (InterruptableProcess r) a -> m (Either (Interrupt NoRecovery) a)
- scheduleMonadIOEff :: MonadIO (Eff r) => Eff (InterruptableProcess r) a -> Eff r (Either (Interrupt NoRecovery) a)
- scheduleIOWithLogging :: HasCallStack => LogWriter IO -> Eff (InterruptableProcess LoggingAndIo) a -> IO (Either (Interrupt NoRecovery) a)
- defaultMainSingleThreaded :: HasCallStack => Eff (InterruptableProcess LoggingAndIo) () -> IO ()
Documentation
Arguments
| :: Monad m | |
| => (forall b. Eff r b -> m b) | |
| -> m () | An that performs a yield w.r.t. the underlying effect
|
| -> Eff (InterruptableProcess 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
schedulePure :: Eff (InterruptableProcess '[Logs, LogWriterReader PureLogWriter]) a -> Either (Interrupt NoRecovery) a Source #
Like scheduleIO but pure. The yield effect is just return ().
schedulePure == runIdentity . scheduleM (Identity . run) (return ())
Since: 0.3.0.2
scheduleIO :: MonadIO m => (forall b. Eff r b -> Eff '[Lift m] b) -> Eff (InterruptableProcess r) a -> m (Either (Interrupt NoRecovery) a) Source #
scheduleMonadIOEff :: MonadIO (Eff r) => Eff (InterruptableProcess r) a -> Eff r (Either (Interrupt NoRecovery) a) Source #
scheduleIOWithLogging :: HasCallStack => LogWriter IO -> Eff (InterruptableProcess LoggingAndIo) 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
defaultMainSingleThreaded :: HasCallStack => Eff (InterruptableProcess LoggingAndIo) () -> IO () Source #
Execute a Process using scheduleM on top of Lift IO and withLogging
String effects.