monad-coroutine-0.9.1: Coroutine monad transformer for suspending and resuming monadic computations
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Coroutine.SuspensionFunctors

Description

This module defines some common suspension functors for use with the Control.Monad.Coroutine module.

Synopsis

Suspension functors

data Yield x y Source #

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 

Instances

Instances details
Functor (Yield x) Source # 
Instance details

Defined in Control.Monad.Coroutine.SuspensionFunctors

Methods

fmap :: (a -> b) -> Yield x a -> Yield x b #

(<$) :: a -> Yield x b -> Yield x a #

newtype Await x y Source #

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) 

Instances

Instances details
Functor (Await x) Source # 
Instance details

Defined in Control.Monad.Coroutine.SuspensionFunctors

Methods

fmap :: (a -> b) -> Await x a -> Await x b #

(<$) :: a -> Await x b -> Await x a #

data Request request response x Source #

The Request functor instance combines a Yield of a request with an Await for a response.

Constructors

Request request (response -> x) 

Instances

Instances details
Functor (Request x f) Source # 
Instance details

Defined in Control.Monad.Coroutine.SuspensionFunctors

Methods

fmap :: (a -> b) -> Request x f a -> Request x f b #

(<$) :: a -> Request x f b -> Request x f a #

data ReadRequest x z Source #

Combines a Yield of a Reader with an Await for a ReadingResult.

Instances

Instances details
Functor (ReadRequest x) Source # 
Instance details

Defined in Control.Monad.Coroutine.SuspensionFunctors

Methods

fmap :: (a -> b) -> ReadRequest x a -> ReadRequest x b #

(<$) :: a -> ReadRequest x b -> ReadRequest x a #

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

type Reader x py y = x -> Reading x py y Source #

data Reading x py y Source #

Constructors

Final x y

Final result chunk with the unconsumed portion of the input

Advance (Reader x py y) y py

A part of the result with the reader of more input and the EOF

Deferred (Reader x py y) y

Reader of more input, plus the result if there isn't any.

eitherFunctor :: (l x -> y) -> (r x -> y) -> Sum l r x -> y Source #

Like either for the Sum data type.

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 #

Weaves the suspensions of a Yield and an Await coroutine together into a plain Identity coroutine. If the Yield coroutine terminates first, the Await one is resumed using the argument default value.

weaveAwaitMaybeYield :: Monad m => WeaveStepper (Await (Maybe x)) (Yield x) Identity m r1 r2 (r1, r2) Source #

Like weaveAwaitYield, except the Await coroutine expects Maybe-wrapped values. After the Yield coroutine terminates, the Await coroutine receives only Nothing.

weaveRequests :: Monad m => x -> y -> WeaveStepper (Request x y) (Request y x) (Yield (x, y)) m r1 r2 (r1, r2) Source #

Weaves two complementary Request coroutine suspensions into a coroutine yielding both requests. If one coroutine terminates before the other, the remaining coroutine is fed the appropriate default value argument.

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.