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

Safe HaskellNone

Control.Monad.Coroutine.Nested

Description

A coroutine can choose to launch 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. A simple coroutine suspension can be converted to a nested one using functions mapSuspension and liftAncestor. To run nested coroutines, use pogoStickNested, or weave with a NestWeaveStepper.

Synopsis

Documentation

data EitherFunctor l r x Source

Combines two alternative functors into one, applying one or the other. Used for nested coroutines.

Constructors

LeftF (l x) 
RightF (r x) 

eitherFunctor :: (l x -> y) -> (r x -> y) -> EitherFunctor l r x -> ySource

Like either for the EitherFunctor data type.

mapNestedSuspension :: (Functor s0, Functor s, Monad m) => (forall y. s y -> s' y) -> Coroutine (EitherFunctor s0 s) m x -> Coroutine (EitherFunctor s0 s') m xSource

Change the suspension functor of a nested Coroutine.

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.

type NestWeaveStepper s0 s1 s2 m x y z = WeaveStepper (EitherFunctor s0 s1) (EitherFunctor s0 s2) s0 m x y zSource

Type of functions capable of combining two child coroutines' CoroutineStepResult values into a parent coroutine. Use with the function weave.

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

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

(Functor d, Functor a, ChildFunctor d, ~ (* -> *) d' (Parent d), AncestorFunctor a d') => AncestorFunctor a d 
Functor a => AncestorFunctor a a 

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.