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

Safe HaskellNone

Control.Monad.Coroutine

Contents

Description

This module defines the Coroutine monad transformer.

A Coroutine monadic computation can suspend its execution at any time, returning control to its invoker. The returned suspension value contains the coroutine's resumption wrapped in a Functor. Here is an example of a coroutine in the IO monad that suspends computation using the functor Yield from the Control.Monad.Coroutine.SuspensionFunctors module:

 producer :: Coroutine (Yield Int) IO String
 producer = do yield 1
               lift (putStrLn "Produced one, next is four.")
               yield 4
               return "Finished"

To continue the execution of a suspended Coroutine, extract it from the suspension functor and apply its resume method. The easiest way to run a coroutine to completion is by using the pogoStick function, which keeps resuming the coroutine in trampolined style until it completes. Here is one way to apply pogoStick to the producer example above:

 printProduce :: Show x => Coroutine (Yield x) IO r -> IO r
 printProduce producer = pogoStick (\(Yield x cont) -> lift (print x) >> cont) producer

Multiple concurrent coroutines can be run as well, and this module provides two different ways. To run two interleaved computations, use a WeaveStepper to weave together steps of two different coroutines into a single coroutine, which can then be executed by pogoStick.

For various uses of trampoline-style coroutines, see

 Coroutine Pipelines - Mario Blažević, The Monad.Reader issue 19, pages 29-50
 Trampolined Style - Ganz, S. E. Friedman, D. P. Wand, M, ACM SIGPLAN NOTICES, 1999, VOL 34; NUMBER 9, pages 18-27

and

 The Essence of Multitasking - William L. Harrison, Proceedings of the 11th International Conference on Algebraic
 Methodology and Software Technology, volume 4019 of Lecture Notes in Computer Science, 2006

Synopsis

Coroutine definition

newtype Coroutine s m r Source

Suspending, resumable monadic computations.

Constructors

Coroutine 

Fields

resume :: m (Either (s (Coroutine s m r)) r)

Run the next step of a Coroutine computation. The result of the step execution will be either a suspension or the final coroutine result.

Instances

type CoroutineStepResult s m r = Either (s (Coroutine s m r)) rSource

suspend :: (Monad m, Functor s) => s (Coroutine s m x) -> Coroutine s m xSource

Suspend the current Coroutine.

Coroutine operations

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

Change the base monad of a Coroutine.

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

Change the suspension functor of a Coroutine.

mapFirstSuspension :: forall s m x. (Functor s, Monad m) => (forall y. s y -> s y) -> Coroutine s m x -> Coroutine s m xSource

Modify the first upcoming suspension of a Coroutine.

Running coroutines

data Naught x Source

The Naught functor instance doesn't contain anything and cannot be constructed. Used for building non-suspendable coroutines.

Instances

runCoroutine :: Monad m => Coroutine Naught m x -> m xSource

Convert a non-suspending Coroutine to the base monad.

bounce :: (Monad m, Functor s) => (s (Coroutine s m x) -> Coroutine s m x) -> Coroutine s m x -> Coroutine s m xSource

Runs a single step of a suspendable Coroutine, using a function that extracts the coroutine resumption from its suspension functor.

pogoStick :: Monad m => (s (Coroutine s m x) -> Coroutine s m x) -> Coroutine s m x -> m xSource

Runs a suspendable Coroutine to its completion.

foldRun :: Monad m => (a -> s (Coroutine s m x) -> (a, Coroutine s m x)) -> a -> Coroutine s m x -> m (a, x)Source

Runs a suspendable coroutine much like pogoStick, but allows the resumption function to thread an arbitrary state as well.

Weaving coroutines together

type PairBinder m = forall x y r. (x -> y -> m r) -> m x -> m y -> m rSource

Type of functions that can bind two monadic values together, used to combine two coroutines' step results. The two functions provided here are sequentialBinder and parallelBinder.

sequentialBinder :: Monad m => PairBinder mSource

A PairBinder that runs the two steps sequentially before combining their results.

parallelBinder :: MonadParallel m => PairBinder mSource

A PairBinder that runs the two steps in parallel.

liftBinder :: forall s m. (Functor s, Monad m) => PairBinder m -> PairBinder (Coroutine s m)Source

Lifting a PairBinder onto a Coroutine monad transformer.

type Weaver s1 s2 s3 m x y z = Coroutine s1 m x -> Coroutine s2 m y -> Coroutine s3 m zSource

Type of functions that can weave two coroutines into a single coroutine.

type WeaveStepper s1 s2 s3 m x y z = Weaver s1 s2 s3 m x y z -> CoroutineStepResult s1 m x -> CoroutineStepResult s2 m y -> Coroutine s3 m zSource

Type of functions capable of combining two coroutines' CoroutineStepResult values into a third one. Module Monad.Coroutine.SuspensionFunctors contains several WeaveStepper examples.

weave :: forall s1 s2 s3 m x y z. (Monad m, Functor s1, Functor s2, Functor s3) => PairBinder m -> WeaveStepper s1 s2 s3 m x y z -> Weaver s1 s2 s3 m x y zSource

Weaves two coroutines into one, given a PairBinder to run the next step of each coroutine and a WeaveStepper to combine the results of the steps.

merge :: forall s m x. (Monad m, Functor s) => (forall y. [m y] -> m [y]) -> (forall y. [s y] -> s [y]) -> [Coroutine s m x] -> Coroutine s m [x]Source

Weaves a list of coroutines with the same suspension functor type into a single coroutine. The coroutines suspend and resume in lockstep.