monad-coroutine-0.7: Coroutine monad transformer for suspending and resuming monadic computations

Control.Monad.Coroutine.Nested

Description

This module defines nestable suspension functors for use with the Coroutine monad transformer, as well as functions for running nested coroutines of this sort.

Coroutines can be run from within another coroutine. In this case, the nested coroutines always suspend to their invoker. If a function from this module, such as pogoStickNested, is used to run a nested coroutine, the parent coroutine can be automatically suspended as well. A single suspension can thus suspend an entire chain of nested coroutines.

Nestable coroutines of this kind should group their suspension functors into an EitherFunctor. You can adjust a normal suspension, such as the one produced by yield, using functions mapSuspension and liftAncestor. To run nested coroutines, use functions pogoStickNested, seesawNested, and coupleNested.

Synopsis

Documentation

pogoStickNested :: forall s1 s2 m x. (Functor s1, Functor s2, Monad m) => (s2 (Coroutine (EitherFunctor s1 s2) m x) -> Coroutine (EitherFunctor s1 s2) m x) -> Coroutine (EitherFunctor s1 s2) m x -> Coroutine s1 m xSource

Run a nested Coroutine that can suspend both itself and the current Coroutine.

coupleNested :: forall s0 s1 s2 m x y. (Monad m, Functor s0, Monad s0, Functor s1, Functor s2) => PairBinder m -> Coroutine (EitherFunctor s0 s1) m x -> Coroutine (EitherFunctor s0 s2) m y -> Coroutine (EitherFunctor s0 (SomeFunctor s1 s2)) m (x, y)Source

Much like couple, but with two nested coroutines.

seesawNested :: (Monad m, Functor s0, Functor s1, Functor s2) => PairBinder m -> SeesawResolver s1 s2 (EitherFunctor s0 s1) (EitherFunctor s0 s2) -> Coroutine (EitherFunctor s0 s1) m x -> Coroutine (EitherFunctor s0 s2) m y -> Coroutine s0 m (x, y)Source

Like seesaw, but for nested coroutines that are allowed to suspend the current coroutine as well as themselves. If both coroutines try to suspend the current coroutine in the same step, the left coroutine's suspension will have precedence.

seesawNestedSteps :: forall m c1 c2 s0 s1 s2 s1' s2' x y. (Monad m, Functor s0, Functor s1, Functor s2, s1' ~ EitherFunctor s0 s1, s2' ~ EitherFunctor s0 s2, c1 ~ Coroutine s1' m x, c2 ~ Coroutine s2' m y) => PairBinder m -> ((c1 -> c2 -> Coroutine s0 m (x, y)) -> Either (s1 c1) x -> Either (s2 c2) y -> Coroutine s0 m (x, y)) -> c1 -> c2 -> Coroutine s0 m (x, y)Source

Like seesawSteps, but for nested coroutines that are allowed to suspend the current coroutine as well as themselves. If both coroutines try to suspend the current coroutine in the same step, the left coroutine's suspension will have precedence.

class Functor c => ChildFunctor c whereSource

Class of functors that can contain another functor.

Associated Types

type Parent c :: * -> *Source

Methods

wrap :: Parent c x -> c xSource

Instances

class (Functor a, Functor d) => AncestorFunctor a d whereSource

Class of functors that can be lifted.

Methods

liftFunctor :: a x -> d xSource

Convert the ancestor functor into its descendant. The descendant functor typically contains the ancestor.

Instances

liftParent :: forall m p c x. (Monad m, Functor p, ChildFunctor c, p ~ Parent c) => Coroutine p m x -> Coroutine c m xSource

Converts a coroutine into a child nested coroutine.

liftAncestor :: forall m a d x. (Monad m, Functor a, AncestorFunctor a d) => Coroutine a m x -> Coroutine d m xSource

Converts a coroutine into a descendant nested coroutine.