simple-effects-0.12.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Yield

Description

The Yield a effect lets a computation produce values of type a during it's execution.

Synopsis

Documentation

newtype Yield a m Source #

Constructors

YieldMethods 

Fields

Instances

Effect (Yield a) Source # 

Associated Types

type CanLift (Yield a :: (* -> *) -> *) (t :: (* -> *) -> * -> *) :: Constraint Source #

Methods

liftThrough :: (CanLift (Yield a) t, Monad m, Monad (t m)) => Yield a m -> Yield a (t m) Source #

mergeContext :: Monad m => m (Yield a m) -> Yield a m Source #

Generic (Yield a m) Source # 

Associated Types

type Rep (Yield a m) :: * -> * #

Methods

from :: Yield a m -> Rep (Yield a m) x #

to :: Rep (Yield a m) x -> Yield a m #

type CanLift (Yield a) t Source # 
type CanLift (Yield a) t = MonadTrans t
type Rep (Yield a m) Source # 
type Rep (Yield a m) = D1 * (MetaData "Yield" "Control.Effects.Yield" "simple-effects-0.12.0.0-7DU8lieKyuzCHjL9A6aZte" True) (C1 * (MetaCons "YieldMethods" PrefixI True) (S1 * (MetaSel (Just Symbol "_yield") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (a -> m ()))))

yield :: forall a m. MonadEffect (Yield a) m => a -> m () Source #

Output a value of type a. The semantics are determined by the implementation, but usually this will block until the next value is requested by the consumer.

implementYieldViaNonDeterminism :: forall a m b. MonadEffect NonDeterminism m => RuntimeImplemented (Yield a) (RuntimeImplemented (Signal a ()) (ExceptT a m)) b -> m a Source #

Implement Yield by using non-determinism to output each of the values. This means you can use the functions from Control.Effects.List to choose how to consume them. For example, using evaluateToList will give you a list of all yielded values. It also means the yield calls won't block since all the values are requested. Other consumer functions give you more control.

implementYieldViaMVar :: forall a m b. (MonadIO m, MonadEffect Async m) => RuntimeImplemented (Yield a) m b -> m (m (Maybe a)) Source #

Implement Yield through an MVar. The result is a monadic action (the inner one) that returns one yielded value or Nothing if the computation is finished. All subsequent calls will also return Nothing. Each execution of this action continues execution in the provided computation, which is otherwise suspended.

If the provided computation forks new threads and doesn't wait for them to finish, Nothing may be returned prematurely (in the sense that maybe there's still a live thread yielding values).

Since the yielding is done through a shared MVar, this implementation is suitable to be run with multiple threads. Scheduling which thread gets continued is defined by the semantics of MVars.

Note
yield will block in this implementation.

implementYieldViaChan :: forall a m b. (MonadIO m, MonadEffect Async m) => RuntimeImplemented (Yield a) m b -> m (m (Maybe a)) Source #

Implements Yield through a Chan. The resulting monadic action (the inner one) reads one value from the queue. Nothing means the provided computation is done. If the provided computation forks new threads and doesn't wait for them to finish, Nothing may be written prematurely (in the sense that maybe there's still a live thread yielding values).

Note
yield will not block in this implementation.

traverseYielded :: Monad m => m (Maybe a) -> (a -> m b) -> m [b] Source #

A convenience function to go through all the yielded results. Use in combination with one of the implementations. Collects a list of values.

traverseYielded_ :: Monad m => m (Maybe a) -> (a -> m b) -> m () Source #

A convenience function to go through all the yielded results. Use in combination with one of the implementations. Discards the computed values.