bluefin-algae-0.1.0.0: Algebraic effects and named handlers in Bluefin.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Bluefin.Algae.Coroutine

Description

Coroutines: yield as an algebraic effect

Iterators

A simple use case of coroutines is as an expressive way of defining iterators.

An iterator is just a program which yields values. The following example yields the integers 1, 2, 3, 4.

range1to4 :: z :> zz => Handler (Coroutine Int ()) z -> Eff zz ()
range1to4 h = do
  yield h 1
  yield h 2
  yield h 3
  yield h 4

The forCoroutine handler is a "for" loop over an iterator, running the loop body for every yielded element. Here we collect the even values into a list stored in mutable State.

filterEven :: z :> zz => Handler (State [Int]) z -> Eff zz ()
filterEven h =
  forCoroutine range1to4 \n ->
    if n `mod` 2 == 0
    then modify h (n :)
    else pure ()

filterEvenResult :: [Int]
filterEvenResult = runPureEff $ execState [] filterEven

-- 1 and 3 are filtered out, 2 and 4 are pushed into the queue
in that order, so they appear in reverse order.
-- filterEvenResult == [4,2]

Cooperative concurrency

Coroutines are "cooperative threads", passing control to other coroutines with explicit yield calls.

In the following example, two threads yield a string back and forth, appending a suffix every time.

pingpong :: Eff ss String
pingpong = withCoroutine coThread mainThread
  where
    coThread z0 h = do
      z1 <- yield h (z0 ++ "pong")
      z2 <- yield h (z1 ++ "dong")
      yield h (z2 ++ "bong")
    mainThread h = do
      s1 <- yield h "ping"
      s2 <- yield h (s1 ++ "ding")
      s3 <- yield h (s2 ++ "bing")
      pure s3

-- runPureEff pingpong == "pingpongdingdongbingbong"

More than two coroutines may be interleaved. In the snippet below, four users pass a string to each other, extending it with breadcrumbs each time.

For example, userLL sends a string to userLR (identified using the Left (Right _) constructors in the yield argument). When userLL receives a second string s' (from anywhere, in this case it will come from userRR), it forwards it to userRL.

echo :: Eff ss String
echo = loopCoPipe ((userLL |+ userLR) |+ (userRL |+ userRR)) (Left (Left "S"))
  where
    userLL = toCoPipe \s h -> do
      s' <- yield h (Left (Right (s ++ "-LL")))  -- send to userLR
      yield h (Right (Left (s' ++ "-LL")))       -- send to userRL
    userLR = toCoPipe \s h -> do
      s' <- yield h (Right (Left (s ++ "-LR")))  -- send to userRL
      yield h (Right (Right (s' ++ "-LR")))      -- send to userRR
    userRL = toCoPipe \s h -> do
      s' <- yield h (Right (Right (s ++ "-RL"))) -- send to userRR
      yield h (Left (Right (s' ++ "-RL")))       -- send to userLR
    userRR = toCoPipe \s h -> do
      s' <- yield h (Left (Left (s ++ "-RR")))   -- send to userLL
      pure (s' ++ "-RR")                           -- terminate
    (|+) = eitherCoPipe id

-- runPureEff echo == "S-LL-LR-RL-RR-LL-RL-LR-RR"

References

Coroutines are also known as generators in Javascript and Python.

Synopsis

Coroutines

Operations

data Coroutine o i :: AEffect where Source #

Coroutine effect with outputs o and inputs i.

Constructors

Yield :: o -> Coroutine o i i

Yield an output and wait for an input.

yield :: z :> zz => Handler (Coroutine o i) z -> o -> Eff zz i Source #

Call the Yield operation.

Handlers

withCoroutine Source #

Arguments

:: forall o i a zz. (i -> ScopedEff (Coroutine o i) zz a) 
-> ScopedEff (Coroutine i o) zz a

Starting coroutine

-> Eff zz a 

Interleave the execution of two coroutines, feeding each one's output to the other's input. Return the result of the first thread to terminate (the other is discarded)

forCoroutine Source #

Arguments

:: forall o i a zz. ScopedEff (Coroutine o i) zz a

Iterator

-> (o -> Eff zz i)

Loop body

-> Eff zz a 

Iterate through a coroutine: execute the loop body o -> Eff zz i for every call to Yield in the coroutine.

Functions

type (:->) = Coroutine Source #

This type synonym rebrands Coroutine into a generic "function" effect, since without the concurrency connotations, the Yield operation looks like a simple function call.

apply :: z :> zz => Handler (a :-> b) z -> a -> Eff zz b Source #

Synonym for yield.

withFunction :: forall a b r zz. (a -> Eff zz b) -> ScopedEff (a :-> b) zz r -> Eff zz r Source #

Interpret (:->) with a function.

Pipes

Definition

newtype Pipe i o m a Source #

Output-first coroutine.

A Pipe represents a coroutine as a state machine: a Pipe yields an output o and waits for an input i, or terminates with a result a.

+--------------+                  +----------------+
| Pipe i o m a | (Yielding o)---> | CoPipe i o m a |
|              | <------(input i) |                |
+--------------+                  +----------------+
       v (Done)
     +---+
     | a |
     +---+

Constructors

MkPipe (m (PipeEvent i o m a)) 

data PipeEvent i o m a Source #

Events of Pipe.

Constructors

Done a

Final result a

Yielding o (CoPipe i o m a)

Output o and continue as CoPipe.

newtype CoPipe i o m a Source #

Input-first coroutine. Pipe continuation.

Constructors

MkCoPipe (i -> Pipe i o m a)

Input i and continue as Pipe.

Unwrap

stepPipe :: Pipe i o m a -> m (PipeEvent i o m a) Source #

Unwrap Pipe.

applyCoPipe :: CoPipe i o m a -> i -> Pipe i o m a Source #

Unwrap CoPipe.

next :: Functor m => CoPipe i o m Void -> i -> m (o, CoPipe i o m Void) Source #

Apply a non-returning CoPipe to yield the next output and CoPipe state.

Constructors

simpleCoPipe :: Functor m => (i -> m o) -> CoPipe i o m void Source #

A CoPipe which runs the same function on every input.

voidCoPipe :: CoPipe Void o m a Source #

CoPipe with no input.

nothingPipe :: Applicative m => Pipe i (Maybe o) m void Source #

Yield Nothing forever.

nothingCoPipe :: Applicative m => CoPipe i (Maybe o) m void Source #

Yield Nothing forever.

Pipe combinators

mapPipe :: Functor m => (i' -> i) -> (o -> o') -> (a -> a') -> Pipe i o m a -> Pipe i' o' m a' Source #

Transform inputs and outputs of a Pipe.

mapCoPipe :: Functor m => (i' -> i) -> (o -> o') -> (a -> a') -> CoPipe i o m a -> CoPipe i' o' m a' Source #

Transform the input and output of a CoPipe.

eitherPipe Source #

Arguments

:: Monad m 
=> (i -> Either i1 i2)

Dispatch input

-> CoPipe i1 o m a

Left copipe

-> Pipe i2 o m a

Right pipe

-> Pipe i o m a 

Sum a copipe and a pipe with the same output type, branching on the input type.

eitherCoPipe Source #

Arguments

:: Functor m 
=> (i -> Either i1 i2)

Dispatch input

-> CoPipe i1 o m a

Left copipe

-> CoPipe i2 o m a

Right copipe

-> CoPipe i o m a 

Sum two copipes with the same output type, branching on the input type.

openPipe :: Applicative m => Pipe i o m () -> Pipe i (Maybe o) m void Source #

Convert a returning Pipe into a non-returning CoPipe, yielding Nothing forever once the end has been reached.

openCoPipe :: Applicative m => CoPipe i o m () -> CoPipe i (Maybe o) m void Source #

Convert a returning CoPipe into a non-returning CoPipe, yielding Nothing forever once the end has been reached.

Destructors

runPipe :: Monad m => CoPipe i o m Void -> Pipe o i m a -> m a Source #

Run a Pipe with a CoPipe to respond to every output.

runCoPipe :: Monad m => CoPipe i o m Void -> CoPipe o i m a -> o -> m a Source #

Run a CoPipe with another CoPipe to respond to every input.

forPipe Source #

Arguments

:: Monad m 
=> Pipe i o m a

Iterator

-> (o -> m i)

Loop body

-> m a 

Iterate through a Pipe. Respond to every Yielding event by running the loop body. Return the final result of the Pipe.

forPipe p g = runPipe (simpleCoPipe g) p

forCoPipe :: Monad m => CoPipe i o m a -> (o -> m i) -> i -> m a Source #

Iterate through a CoPipe.

loopPipe :: Monad m => Pipe o o m a -> m a Source #

Loop the output of a pipe back to its input.

loopCoPipe :: Monad m => CoPipe o o m a -> o -> m a Source #

Forward the output of a CoPipe to its input.

feedPipe :: Monad m => [i] -> Pipe i o m a -> m [o] Source #

Run a Pipe with a fixed number of inputs.

feedCoPipe :: Monad m => [i] -> CoPipe i o m a -> m [o] Source #

Run a CoPipe with a fixed number of inputs.

Handlers involving pipes

Using the handlers toCoPipe and toPipe as primitives, we can define the other handlers.

withCoroutine g f = runPipe (toCoPipe g) (toPipe f)
forCoroutine g f = runPipe (simpleCoPipe g) (toPipe f)
withCoPipe g f = runPipe g (toPipe f)

type CoPipeSEff i o zz a = i -> ScopedEff (Coroutine o i) zz a Source #

Representation of CoPipe as scoped Eff computations.

toCoPipe :: forall o i a zz. CoPipeSEff i o zz a -> CoPipe i o (Eff zz) a Source #

Convert a coroutine that doesn't return into a CoPipe.

type PipeSEff i o zz a = ScopedEff (Coroutine o i) zz a Source #

Representation of Pipe as scoped Eff computations.

toPipe :: forall o i a zz. PipeSEff i o zz a -> Pipe i o (Eff zz) a Source #

Evaluate a coroutine into a Pipe.

withCoPipe Source #

Arguments

:: forall o i a zz. CoPipe i o (Eff zz) a 
-> ScopedEff (Coroutine i o) zz a

Starting coroutine

-> Eff zz a 

Interleave the execution of a copipe and a coroutine.

Interpreting pipes as coroutines

type CoPipeEff i o zz a = forall z. z :> zz => i -> Handler (Coroutine o i) z -> Eff zz a Source #

Representation of CoPipe as Eff computations.

fromCoPipe :: CoPipe i o (Eff zz) a -> CoPipeEff i o zz a Source #

Convert a CoPipe into a coroutine.

type PipeEff i o zz a = forall z. z :> zz => Handler (Coroutine o i) z -> Eff zz a Source #

Representation of Pipe as Eff computations.

fromPipe :: Pipe i o (Eff zz) a -> PipeEff i o zz a Source #

Convet a Pipe into a coroutine.