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

[ concurrency, control, library, monads ] [ Propose Tags ]

This package defines a monad transformer, applicable to any monad, that allows the monadic computation to suspend and to be later resumed. The transformer is parameterized by an arbitrary functor, used to store the suspended computation's resumption.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.5, 0.5.1, 0.6, 0.6.1, 0.7, 0.7.1, 0.8, 0.8.0.1, 0.9, 0.9.0.1, 0.9.0.2, 0.9.0.3, 0.9.0.4, 0.9.1, 0.9.1.1, 0.9.1.2, 0.9.1.3, 0.9.2
Dependencies base (>=4.9 && <5), monad-parallel (<1.0), transformers (>=0.2 && <0.7), transformers-compat (>=0.3 && <0.8) [details]
License LicenseRef-GPL
Copyright (c) 2010-2018 Mario Blazevic
Author Mario Blazevic
Maintainer blamario@protonmail.com
Category Concurrency, Control, Monads
Home page https://hub.darcs.net/blamario/SCC.wiki/
Source repo head: darcs get https://hub.darcs.net/blamario/SCC/
Uploaded by MarioBlazevic at 2022-03-23T15:13:55Z
Distributions LTSHaskell:0.9.2, NixOS:0.9.2, Stackage:0.9.2
Reverse Dependencies 10 direct, 2 indirect [details]
Downloads 12563 total (66 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2022-03-23 [all 1 reports]

Readme for monad-coroutine-0.9.2

[back to package description]

The monad-coroutine library, implemented by the Control.Monad.Coroutine module, provides a limited coroutine functionality in Haskell. The centerpiece of the approach is the monad transformer Coroutine, which transforms an arbitrary monadic computation into a suspendable and resumable one. The basic definition is simple:

newtype Coroutine s m r = Coroutine {resume :: m (Either (s (Coroutine s m r)) r)}

instance (Functor s, Monad m) => Monad (Coroutine s m) where
  return = Coroutine . return . Right
  t >>= f = Coroutine (resume t >>= either (return . Left . fmap (>>= f)) (resume . f))

Suspension Functors

The Coroutine transformer type is parameterized by a functor. The functor in question wraps the resumption of a suspended coroutine, and it can carry other information as well. Module Control.Monad.Coroutine.SuspensionFunctors exports some useful functors, one of which is Yield:

data Yield x y = Yield x y
instance Functor (Yield x) where
  fmap f (Yield x y) = Yield x (f y)

A coroutine parameterized by this functor is a generator which yields a value every time it suspends. For example, the following function generates the program's command-line arguments:

genArgs :: Coroutine (Yield String) IO ()
genArgs = getArgs >>= mapM_ yield

The Await functor is dual to Yield; a coroutine that suspends using this functor is a consumer coroutine that on every suspension expects to be given a value before it resumes. The following example is a consumer coroutine that prints every received value to standard output:

printer :: Show x => Coroutine (Await x) IO ()
printer = await >>= print >> printer           

While these two are the most obvious suspension functors, any functor whatsoever can be used as a coroutine suspension functor.

Running a coroutine

After a coroutine suspends, the suspension functor must be unpacked to get to the coroutine resumption. Here's an example of how the printer example could be run:

printerFeeder :: Show x => [x] -> Coroutine (Await x) IO () -> IO ()
printerFeeder [] _ = return ()
printerFeeder (head:tail) printer = do p <- resume printer
                                       case p of Left (Await p') -> printerFeeder tail (p' head)
                                                 Right result -> return result

Alternatively, you can use the function pogoStick or foldRun to the same effect:

printerFeeder feed printer = liftM snd $ foldRun f feed printer
  where f (head:tail) (Await p) = (tail, p head)
        f []          _         = ([], return ())