Difference between revisions of "MonadCont under the hood"

From HaskellWiki
Jump to navigation Jump to search
m
m
Line 19: Line 19:
 
<hask>Cont</hask> objects can be chained together, so that the continuation you pass in threads through the guts of all the <hask>Cont</hask> objects in the chain before it's finally invoked. The way they chain is the way <hask>Cont</hask> works: each object in the chain invokes a continuation that ''has the next object's computation prepended to the final continuation''. Let's say we have a chain of <hask>Cont</hask> objects <hask>F1 -> F2 -> F3</hask>, and let's say you had a continuation <hask>C3</hask> that you want to pass to the chain. Then:
 
<hask>Cont</hask> objects can be chained together, so that the continuation you pass in threads through the guts of all the <hask>Cont</hask> objects in the chain before it's finally invoked. The way they chain is the way <hask>Cont</hask> works: each object in the chain invokes a continuation that ''has the next object's computation prepended to the final continuation''. Let's say we have a chain of <hask>Cont</hask> objects <hask>F1 -> F2 -> F3</hask>, and let's say you had a continuation <hask>C3</hask> that you want to pass to the chain. Then:
   
* <hask>F3</hask> needs to invoke <hask>C3</hask>when it's done
+
* <hask>F3</hask> needs to invoke <hask>C3</hask> when it's done.
 
* <hask>F2</hask> needs to invoke a continuation <hask>C2</hask> that will invoke <hask>F3</hask>, which will invoke <hask>C3</hask>.
 
* <hask>F2</hask> needs to invoke a continuation <hask>C2</hask> that will invoke <hask>F3</hask>, which will invoke <hask>C3</hask>.
 
* <hask>F1</hask> needs to invoke a continuation <hask>C1</hask>,<br/>&nbsp;which will invoke <hask>F2</hask>,<br/>&nbsp;&nbsp;which will invoke <hask>C2</hask>,<br/>&nbsp;&nbsp;&nbsp;which will invoke <hask>F3</hask>,<br/>&nbsp;&nbsp;&nbsp;&nbsp;which will finally invoke <hask>C3</hask>.
 
* <hask>F1</hask> needs to invoke a continuation <hask>C1</hask>,<br/>&nbsp;which will invoke <hask>F2</hask>,<br/>&nbsp;&nbsp;which will invoke <hask>C2</hask>,<br/>&nbsp;&nbsp;&nbsp;which will invoke <hask>F3</hask>,<br/>&nbsp;&nbsp;&nbsp;&nbsp;which will finally invoke <hask>C3</hask>.

Revision as of 03:16, 24 July 2010

This tutorial is a response to the following Stack Overflow question. There's a short but useful description of Cont and MonadCont operations in the Control.Monad.Cont documentation, but it doesn't really describe how the continuation monad does its thing. This is an attempt at much more detailed explanation of what Cont and MonadCont are doing under the hood.

This tutorial assumes a working knowledge of Haskell, though of course it doesn't assume that you understood the implementation of Control.Monad.Cont the first time you read it!

Introducing Continuations and the Cont type

Continuations are functions that represent "the remaining computation to do." Their representation here is a -> r, which is simply a function that takes some value produced by the current computation, of some type a, and returns the final result of type r from it.

The type Cont r a (instances of which I will, in this tutorial, refer to as Cont objects) represents a continuation-passing-style function that takes a single continuation as its only input. In other words, its guts are a function that:

  1. takes a continuation as an argument
  2. does whatever it needs to do
  3. produces a value of type r at the end, presumably by invoking the continuation.

Note that whatever it needs to do, i.e. whatever values it needs to be able to use to do its thing, must already be bound up into the Cont object. So, generally, we won't be dealing with Cont objects directly, but with functions that can ultimately produce one.

Sequencing Continuation-Style Computations

Applicative Sequencing

Cont objects can be chained together, so that the continuation you pass in threads through the guts of all the Cont objects in the chain before it's finally invoked. The way they chain is the way Cont works: each object in the chain invokes a continuation that has the next object's computation prepended to the final continuation. Let's say we have a chain of Cont objects F1 -> F2 -> F3, and let's say you had a continuation C3 that you want to pass to the chain. Then:

  • F3 needs to invoke C3 when it's done.
  • F2 needs to invoke a continuation C2 that will invoke F3, which will invoke C3.
  • F1 needs to invoke a continuation C1,
     which will invoke F2,
      which will invoke C2,
       which will invoke F3,
        which will finally invoke C3.

What I've described so far is the applicative operation of continuations.

Extending to Monad

With the Monad operation there's an extra wrinkle: we allow for the value of one computation to affect which Cont object gets invoked next. In this world:

  • return takes a value and produces a Cont object that just passes that value to its continuation.
  • bind takes a Cont object, and a function that produces another Cont object given a value from the first, and chains them together into one Cont object. That object, when invoked, is going to:
    • take a single continuation object C,
    • produce an intermediate value,
    • use that intermediate value to select/create the next Cont object to invoke,
    • invoke that Cont object with C

Understanding the Monad

Return

The code:

    return a = Cont ($ a)

is equivalent to the following code:

    return a = Cont $ \c -> c a

Why? The code ($ a) is a slice of the operator $, which represents application. In other words, ($ a) can be equivalently written \f -> f a, or "take a function as input and apply it to a."

Thus, return in the Cont monad passes the result of its computation directly to the continuation it's given.

Bind

The code:

    m >>= k = Cont $ \c -> runCont m $ \a -> runCont (k a) c

is a terse way of saying the following:

    m >>= k = let s c = runCont m c
                  t c = \a -> runCont (k a) c
              in Cont $ \c -> s (t c)

Do you see what's happening? (k a) has become part of the continuation that m is given, and m passes its value to k by simply passing its value to its continuation. The Cont objects are being created "just in time" to be used, based on the computation so far.

Exploring the Monad

Here's a simple example I've cooked up that should help illustrate the monad in action:

    f :: Int -> Cont r Int
    f x = Cont $ \c -> c (x * 3)
    g :: Int -> Cont r Int
    g x = Cont $ \c -> c (x - 2)

These are simple functions that produce Cont objects, given an intermediate value x. You can see that the value being passed to the continuation is an Int, though we don't put any restrictions on what that continuation can ultimately produce.

BTW, they can be equivalently written as:

    f x = return (x * 3)
    g x = return (x - 2)

where they look very similar to normal functions. I'm writing them longhand to show you explicitly what the functions are doing.

    h :: Int -> Cont r Int
    h x | x == 5 = f x
        | otherwise = g x

This is a more complicated function that chooses between two other Cont objects, based on the input it's given.

Now let's create a top-level Cont object that does some chaining:

    doC :: Cont r Int
    doC = return 5 >>= h

And we'll invoke it like this:

    finalC :: Show a => a -> String
    finalC x = "Done: " ++ show(x)
    
    runCont doC finalC

Note that runCont doC produces a function of type (Int -> a) -> a, which is invoked on a continuation of type Show a => a -> String, which reduces in this context to Int -> String. The final value produced will be a String. Can you guess what it will say? What if you changed return 5 to return 4?

Let's see if you're right:

return 5 produces a Cont object that basically looks like this: Cont $ \c -> c 5. So that part is easy.

h is a function that takes a value and produces a Cont object depending on the value it's given.

Lemma: runCont Cont $ effectively cancels out, i.e. runCont (Cont $ \c -> ...) is simply the function \c -> .... This is because runCont is a field selector of Cont objects, and Cont objects only have that one field.

Therefore, (return 5) >>= h expands and simplifies to:

    let s c = c 5
        t c = \a -> runCont (h a) c
    in Cont $ \c -> s (t c)

And finally, runCont doC finalC evaluates to:

   runCont doC finalC
   => runCont (Cont $ \c -> s (t c)) finalC  -- unfold doC
   => s (t finalC)                           -- simplify with lemma and apply to finalC
   => (t finalC) 5                           -- unfold s
   => (\a -> runCont (h a) finalC) 5         -- unfold t
   => runCont (h 5) finalC                   -- apply \a... to 5
   => runCont (f 5) finalC                   -- unfold h
   => runCont (Cont $ \c -> c (5*3)) finalC  -- unfold f
   => (\c -> c (5*3)) finalC                 -- simplify with lemma
   => finalC (5*3)                           -- apply \c... to finalC
   => "Done: 15"                             -- apply *; apply finalC to final value!

MonadCont and callCC

One final extension to this which is frequently used is the MonadCont class, which provides a callCC operation. callCC creates a Cont object that invokes a function to construct a Cont object, and then runs it with the continuation it's given. However, it provides that function an alternate continuation that can be invoked to "break out" of the computation and simply pass a value to the continuation that was active when callCC was invoked. This function's operation is definitely easier to understand by seeing it in action. Evaluate the following code, replacing the corresponding functions above:

    h :: Int -> (Int -> Cont r Int) -> Cont r Int
    h x abort | x == 5 = f x
              | otherwise = abort (-1)
    
    doC n = return n >>= \x -> 
            callCC (\abort -> h x abort) >>= \y ->
            g y

Run runCont (doC 5) finalC. h should invoke f, and g will be invoked afterward, so you should get 13 as the final answer.

Now change (doC 5) to (doC 4). In this case, h will call abort, which passes -1 to g. -3 should be the final answer.

Now change doC to move g inside the callCC abort context:

    doC n = return n >>= \x ->
            callCC (\abort -> h x abort >>= \y ->
                              g y)

and run with (doC 4). In this case, h invokes abort and g is never invoked! -1 is the final answer.

Once you've converted all your operations to continuation-passing style by putting them in the Cont monad, and have a handle on how >>= works in that monad, understanding how callCC works is surprisingly simple:

    callCC f = Cont $ \c -> runCont (f (\a -> Cont $ \_ -> c a )) c

can be written as

    callCC f = let backtrack a = Cont $ \_ -> c a
               in Cont $ \c -> runCont (f backtrack) c

The key is backtrack, which takes whatever "inner" continuation is active when backtrack is invoked, completely ignores it, and simply passes its value to the "outer" continuation c. (Compare this to the definition of return, which always uses the continuation it's given.) fis the function passed to callCC, whose extent provides the context under which backtrack can be used.