Probabilistic Effects. λθ

Coroutines

Coroutines are the act of cooperatively passing control around.

Monad-Coroutine

Monads as Imperative Languages

Haskell provides do notation which is syntactic sugar to facilitate imperative programming. The monad of a do block specifies the imperative language which is typically equipped with actions. Monad transformers are then language enhancers. They add additional actions to an underlying language.

The Pause transformer

The Pause monad transformer will augment the underlying language with one additional action: pause. This way, we will be able to build an action which can run for a while, and then pause itself when it reaches a checkpoint. At that point, it will produce a new action which can be run to continue where it left off until the next pause point.

data Pause m = Run (m (Pause m)) | Done

pauseExample :: Pause IO
pauseExample = Run $ do
  putStrLn "Start"
  putStrLn "Step 1"
  return $ Run $ do
    putStrLn "Step 2"
    return $ Run $ do
      putStrLn "Step 3"
      putStrLn "Done"
      return Done

We would then like to be able to step these actions, or perhaps ignore the pauses and run the sequence of actions to completion.

The function runN runs n steps of computations. When encountering a Run m, this embeds a monad m containing an action – calling >>= on m then runs the monadic action.

runN :: Monad m => Int -> Pause m -> m (Pause m)
runN 0 p    = return p
runN _ Done = return Done
runN n (Run m)
  | n < 0     = fail "Invalid argument to runN"
  | otherwise = m >>= runN (n - 1)

The function fullRun runs all steps of computations until reaching Done.

fullRun :: Monad m => Pause m -> m ()
fullRun Done    = return ()
fullRun (Run m) = m >>= fullRun

To make Pause a monad transformer, we need to add a result to the Done constructor.

data PauseT m r = RunT (m (PauseT m r)) | DoneT r

PauseT adds a way for us to pause ourselves, and wait patiently for whoever is “in charge” to resume us.

Coroutines

The Coroutine monad transformer is:

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

data CoroutineStepResult s m r
  = Run (s (Coroutine s m r))
  | Done r

The s type parameter is called the suspension functor. From the Run constructor of CoroutineStepResult, we can see that when a coroutine suspends itself, it will present us with the suspension functor which may contain a way to resume it or not (depending on the functor).

Calling resume runs the next step of a Coroutine computation. The result of the step execution will either be a suspension s (Coroutine s m r) or the final coroutine result r.

Coroutine comes with one primary command suspend. Calling suspend will suspend the current Coroutine computation by wrapping up a suspension functor into the Coroutine monad.

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

Interface: Suspension Functor

PauseF is an example of a specific suspension functor.

newtype PauseF x = PauseF x

instance Functor PauseF where
  fmap f (PauseF x) = PauseF (f x)

type PauseT = Coroutine PauseF

pause :: Monad m => PauseT m ()
pause = suspend $ PauseF (return ())

We can enhance PauseF in two ways: by allowing suspensions to provide an output value o, and allowing suspensions to take in an input value i, before moving on with the next step.

data Interface i o x = Produced o (i -> x)

instance Functor (Interface i o) where
  fmap f (Produced o k) = Produced o (f . k)

Note that by setting the input and output parameters to the message (), we can recover PauseT.

type PauseF' = Interface () ()

type PauseT' = Coroutine PauseF'

pause' :: Monad m => PauseT' m ()
pause' = suspend $ Produced () (\() -> return ())

Producing and Consuming Coroutines

Coroutines are in one of two states: producing or consuming.

  • In the producing state, they require no input and should be run until they produce something, at which point they switch to the consuming state.
  • In the consuming state, they require an input – after receiving an input, they switch to the producing state.
type Producing o i = Coroutine (Interface i o)
type Consuming r m i o = i -> Producing o i m r

In this abstraction from Monad.Coroutine, even though there is an input end and an output end on an Interface, this is not the same as the abstractions which the pipes or conduits libraries use. The main difference is that an Interface always bundles a single output with a single input. Although our output type can have multiple components, we always have to surrender control with a single value, and control returns to us with a single value.

There are two main operations that this abstraction gives us.

  • One is the action yield, which is similar to pause but communicates information across the interface.
  • The other is a combining operator $$ which attaches a Producing coroutine to a Consuming coroutine with compatible interfaces.
newtype Coroutine s m r = Coroutine { resume :: m (CoroutineState s m r) }

data CoroutineState s m r = Run (s (Coroutine s m r)) | Done r

instance (Functor s, Functor m) => Functor (Coroutine s m) where
  fmap f 

Last updated on 13 Nov 2020
Published on 13 Nov 2020