Difference between revisions of "User:Benmachine/Cont"

From HaskellWiki
Jump to navigation Jump to search
Line 84: Line 84:
 
=== So what's callCC? ===
 
=== So what's callCC? ===
   
"Call with current continuation". I don't really get the name. Basically, you use <hask>callCC</hask> like this:
+
"Call with current continuation". Basically, you use <hask>callCC</hask> like this:
   
 
<haskell>
 
<haskell>

Revision as of 01:31, 20 January 2012

A practical Cont tutorial

It seems to me like Cont and ContT is way simpler than people make it. I think it's just a way to give a name to the "tail" of a do-block.

contstuff :: Magic
contstuff = do
  thing1
  thing2
  -- Now I want to manipulate the rest of the computation.
  -- So I want a magic function that will give me the future to
  -- play with.
  magic $ \rest ->
    -- 'rest' is the rest of the computation. Now I can just do it,
    -- or do it twice and combine the results, or discard it entirely,
    -- or do it and then use the result to do it again... it's easy to
    -- imagine why this might be useful.
    messAboutWith rest

  thing3 -- these might get done once, several times,
  thing4 -- or not at all.

The question is, what type should magic have? Well, let's say the whole do-block results in a thing of type r (without thinking too hard about what this means). Then certainly the function we give magic should result in type r as well, since it can run that do-block. The function should also accept a single parameter, referring to the tail of the computation. That's the rest of the do-block, which has type r, right? Well, more or less, with one caveat: we might bind the result of magic:

  x <- magic $ \rest -> -- ...
  thingInvolving x

so the rest of the do-block has an x in it that we need to supply (as well as other variables, but magic already has access to those). So the rest of the do-block can be thought of as a bit like a -> r. Given access to the rest of that do-block, we need to produce something of type r. So our lambda has type (a -> r) -> r and hence magic :: (a -> r) -> r -> Magic... oh but this looks familiar...

newtype Cont r a = Cont { runCont :: (a -> r) -> r }
-- Magic = Cont r a

magic = Cont

Tada! The moral of the story is, if you got up one morning and said to yourself "I want to stop in the middle of a do-block and play about with the last half of it", then Cont is the type you would have come up with.


Now you know what the Cont type is, you can implement pretty much all of its type class instances just from there, since the types force you to apply this to that and compose that with this. But that doesn't really help you to understand what's going on: here's a way of using the intuition introduced above to implement `Functor` without thinking about the types too much:

instance Functor (Cont r) where
  fmap f (Cont g) = -- ...

Well, we've got to build a Cont value, and those always start the same way:

  fmap f (Cont g) = Cont $ \rest -> -- ...

Now what? Well, remember what g is. It comes from inside a Cont, so it looks like \rest -> stuffWith (rest val), where val is the 'value' of the computation (what would be bound with <-). So we want to give it a rest, but we don't want it to be called with the 'value' of the computation - we want f to be applied to it first. Well, that's easy:

  fmap f (Cont x) = Cont $ \rest -> x (\val -> rest (f val))

Load it in `ghci` and the types check. Amazing! Emboldened, let's try Applicative

instance Applicative (Cont r) where
  pure x = Cont $ \rest -> -- ...

We don't want to do anything special here. The rest of the computation wants a value, let's just give it one:

  pure x = Cont $ \rest -> rest x

What about <*>?

  Cont f <*> Cont x = Cont $ \rest -> -- ...

This is a little trickier, but if we look at how we did fmap we can guess at how we get the function and the value out to apply one to the other:

  Cont f <*> Cont x = Cont $ \rest -> f (\fn -> x (\val -> rest (fn val)))

Monad is a harder challenge, but the same basic tactic applies. Hint: remember to unwrap the newtype with runCont, case, or let when necessary.

So what's callCC?

"Call with current continuation". Basically, you use callCC like this:

  ret <- callCC $ \exit -> do
    -- A mini Cont block.
    -- You can bind things to ret in one of two ways: either return
    -- something at the end as usual, or call exit with something of
    -- the appropriate type, and the rest of the block will be ignored.
    when (n < 10) $ exit "small!"
    when (n > 100) $ exit "big!"
    return "somewhere in between!"

See if you can work out the type (not too hard: work out the type of exit first, then the do block) then the implementation. Try not to follow the types too much: they will tell you what to write, but not why. Think instead about the strategies we used above, and what each bit means. Hints: remember that exit throws stuff away, and remember to use runCont or similar, as before.

What about ContT?

The thing to understand with ContT is that it's exactly the same trick. Literally. To the point where I think the following definition works fine:

newtype ContT r m a = ContT (Cont (m r) a)
  deriving (Functor, Applicative, Monad)

runContT :: ContT r m a -> (a -> m r) -> m r
runContT (ContT m) = runCont m

The only reason the newtype exists at all is to shuffle the type parameters around a bit, so that instances of things like MonadTrans can be defined.

Some real examples

The examples in the mtl doc are unconvincing. They don't do anything genuinely daring. Some of them work in any monad! Here's a more complex example:

-- This tends to be useful.
runC :: Cont a a -> a
runC c = runCont c id

faff :: Integer -> Maybe Integer
faff n = runC $ do
  test <- Cont $ \try -> case try n of 
    Nothing -> try (2*n) 
    res -> fmap (subtract 10) res
  return $ if test < 10 then Nothing else Just test

The return statement is run with test = n: if it succeeds then we subtract 10 from the result and return it. If it fails we try again, but with (2*n): note that if this succeeds, we don't subtract 10.

As an exercise, work out how to make the function return (a) Nothing, (b) Just 12, (c) Just 0.

Acknowledgements

I think it was the legendary sigfpe who made this click for me, after thinking about how this works:

and there's also this:

which is more-or-less the above trick but in a bit more detail.

Disclaimer

I'm currently unsure if I've fallen victim to Brent's (in)famous monad tutorial fallacy. I know that there was more in my learning process than I've been able to reproduce above, but I do think I'm doing this in a genuinely new style – Cont always seems to be presented in such vague terms, and people don't provide actual examples of the way it works.

A moderately heretical conclusion

Sometimes looking at types isn't the best way to understand things! I've implemented the Cont type class instances before, and the types ensure that you pretty much can't help but do it the right way. But that doesn't tell you what you're doing, or why you did it that way. I never understood Cont until I came across the natural interpretation of its content. It's a bit like fitting the pieces of a puzzle together without looking at the picture.