Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 a Sum
. 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
- eitherFunctor :: (l x -> y) -> (r x -> y) -> Sum l r x -> y
- mapNestedSuspension :: (Functor s0, Functor s, Monad m) => (forall y. s y -> s' y) -> Coroutine (Sum s0 s) m x -> Coroutine (Sum s0 s') m x
- pogoStickNested :: forall s1 s2 m x. (Functor s1, Functor s2, Monad m) => (s2 (Coroutine (Sum s1 s2) m x) -> Coroutine (Sum s1 s2) m x) -> Coroutine (Sum s1 s2) m x -> Coroutine s1 m x
- type NestWeaveStepper s0 s1 s2 m x y z = WeaveStepper (Sum s0 s1) (Sum s0 s2) s0 m x y z
- class Functor c => ChildFunctor c where
- class (Functor a, Functor d) => AncestorFunctor a d where
- liftFunctor :: a x -> d x
- liftParent :: forall m p c x. (Monad m, Functor p, ChildFunctor c, p ~ Parent c) => Coroutine p m x -> Coroutine c m x
- liftAncestor :: forall m a d x. (Monad m, Functor a, AncestorFunctor a d) => Coroutine a m x -> Coroutine d m x
Documentation
eitherFunctor :: (l x -> y) -> (r x -> y) -> Sum l r x -> y Source #
mapNestedSuspension :: (Functor s0, Functor s, Monad m) => (forall y. s y -> s' y) -> Coroutine (Sum s0 s) m x -> Coroutine (Sum s0 s') m x Source #
Change the suspension functor of a nested Coroutine
.
pogoStickNested :: forall s1 s2 m x. (Functor s1, Functor s2, Monad m) => (s2 (Coroutine (Sum s1 s2) m x) -> Coroutine (Sum s1 s2) m x) -> Coroutine (Sum s1 s2) m x -> Coroutine s1 m x Source #
type NestWeaveStepper s0 s1 s2 m x y z = WeaveStepper (Sum s0 s1) (Sum s0 s2) s0 m x y z Source #
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 where Source #
Class of functors that can contain another functor.
class (Functor a, Functor d) => AncestorFunctor a d where Source #
Class of functors that can be lifted.
liftFunctor :: a x -> d x Source #
Convert the ancestor functor into its descendant. The descendant functor typically contains the ancestor.
Instances
(Functor a, ChildFunctor d, d' ~ Parent d, AncestorFunctor a d') => AncestorFunctor a d Source # | |
Defined in Control.Monad.Coroutine.Nested liftFunctor :: a x -> d x Source # | |
Functor a => AncestorFunctor a a Source # | |
Defined in Control.Monad.Coroutine.Nested liftFunctor :: a x -> a x Source # |
liftParent :: forall m p c x. (Monad m, Functor p, ChildFunctor c, p ~ Parent c) => Coroutine p m x -> Coroutine c m x Source #
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 x Source #
Converts a coroutine into a descendant nested coroutine.