| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.Coroutine.SuspensionFunctors
Description
This module defines some common suspension functors for use with the Control.Monad.Coroutine module.
- data Yield x y = Yield x y
- newtype Await x y = Await (x -> y)
- data Request request response x = Request request (response -> x)
- data ReadRequest x z
- data ReadingResult x py y- = ResultPart py (Reader x py y)
- | FinalResult y
 
- type Reader x py y = x -> Reading x py y
- data Reading x py y
- eitherFunctor :: (l x -> y) -> (r x -> y) -> Sum l r x -> y
- yield :: Monad m => x -> Coroutine (Yield x) m ()
- await :: Monad m => Coroutine (Await x) m x
- request :: Monad m => x -> Coroutine (Request x y) m y
- requestRead :: (Monad m, Monoid x) => Reader x py y -> Coroutine (ReadRequest x) m (ReadingResult x py y)
- concatYields :: (Monad m, Foldable f) => Coroutine (Yield (f x)) m r -> Coroutine (Yield x) m r
- concatAwaits :: (Monad m, Foldable f) => Coroutine (Await x) m r -> Coroutine (Await (f x)) m r
- weaveAwaitYield :: Monad m => x -> WeaveStepper (Await x) (Yield x) Identity m r1 r2 (r1, r2)
- weaveAwaitMaybeYield :: Monad m => WeaveStepper (Await (Maybe x)) (Yield x) Identity m r1 r2 (r1, r2)
- weaveRequests :: Monad m => x -> y -> WeaveStepper (Request x y) (Request y x) (Yield (x, y)) m r1 r2 (r1, r2)
- weaveReadWriteRequests :: (Monad m, Monoid x) => WeaveStepper (ReadRequest x) (Request x x) Identity m r1 r2 (r1, r2)
- weaveNestedReadWriteRequests :: (Monad m, Functor s, Monoid x) => NestWeaveStepper s (ReadRequest x) (Request x x) m r1 r2 (r1, r2)
Suspension functors
The Yield functor instance is equivalent to (,) but more descriptive. A coroutine with this suspension functor
 provides a value with every suspension.
Constructors
| Yield x y | 
The Await functor instance is equivalent to (->) but more descriptive. A coroutine with this suspension functor
 demands a value whenever it suspends, before it can resume its execution.
Constructors
| Await (x -> y) | 
data ReadRequest x z Source
Combines a Yield of a Reader with an Await for a ReadingResult.
Instances
| Functor (ReadRequest x) | 
data ReadingResult x py y Source
Constructors
| ResultPart py (Reader x py y) | A part of the result with the reader of more input | 
| FinalResult y | Final result chunk | 
eitherFunctor :: (l x -> y) -> (r x -> y) -> Sum l r x -> y Source
yield :: Monad m => x -> Coroutine (Yield x) m () Source
Suspend the current coroutine yielding a value.
await :: Monad m => Coroutine (Await x) m x Source
Suspend the current coroutine until a value is provided.
request :: Monad m => x -> Coroutine (Request x y) m y Source
Suspend yielding a request and awaiting the response.
requestRead :: (Monad m, Monoid x) => Reader x py y -> Coroutine (ReadRequest x) m (ReadingResult x py y) Source
Suspend yielding a ReadRequest and awaiting the ReadingResult.
Utility functions
concatYields :: (Monad m, Foldable f) => Coroutine (Yield (f x)) m r -> Coroutine (Yield x) m r Source
Converts a coroutine yielding collections of values into one yielding single values.
concatAwaits :: (Monad m, Foldable f) => Coroutine (Await x) m r -> Coroutine (Await (f x)) m r Source
Converts a coroutine awaiting single values into one awaiting collections of values.
WeaveSteppers for weaving pairs of coroutines
weaveAwaitYield :: Monad m => x -> WeaveStepper (Await x) (Yield x) Identity m r1 r2 (r1, r2) Source
weaveAwaitMaybeYield :: Monad m => WeaveStepper (Await (Maybe x)) (Yield x) Identity m r1 r2 (r1, r2) Source
weaveRequests :: Monad m => x -> y -> WeaveStepper (Request x y) (Request y x) (Yield (x, y)) m r1 r2 (r1, r2) Source
weaveReadWriteRequests :: (Monad m, Monoid x) => WeaveStepper (ReadRequest x) (Request x x) Identity m r1 r2 (r1, r2) Source
The consumer coroutine requests input through ReadRequest and gets ReadingResult in response. The producer
 coroutine receives the unconsumed portion of its last requested chunk as response.
weaveNestedReadWriteRequests :: (Monad m, Functor s, Monoid x) => NestWeaveStepper s (ReadRequest x) (Request x x) m r1 r2 (r1, r2) Source
Like weaveReadWriteRequests but for nested coroutines.