Wednesday, December 24, 2008

The Mother of all Monads

Suppose someone stole all the monads but one, which monad would you want it to be? If you're a Haskell programmer you wouldn't be too bothered, you could just roll your own monads using nothing more than functions.

But suppose someone stole do-notation leaving you with a version that only supported one type of monad. Which one would you choose? Rolling your own Haskell syntax is hard so you really want to choose wisely. Is there a universal monad that encompasses the functionality of all other monads?

I often find I learn more computer science by trying to decode random isolated sentences than from reading entire papers. About a year ago I must have skimmed this post because the line "the continuation monad is in some sense the mother of all monads" became stuck in my head. So maybe Cont is the monad we should choose. This post is my investigation of why exactly it's the best choice. Along the way I'll also try to give some insight into how you can make practical use the continuation monad. I'm deliberately going to avoid discussing the underlying mechanism that makes continuations work.

So let's start with this simple piece of code


> import Control.Monad.Cont

> ex1 = do
> a <- return 1
> b <- return 10
> return $ a+b


I haven't specified the monad but in almost every case we'd expect the result to have something to do with the number 11. For the list monad we get [11], for the Maybe monad we get Just 11 and so on. For the Cont monad we get something that takes a function, and applies it to 11. Here's an example of its use:


> test1 = runCont ex1 show


ex1 is just a function that takes as argument show and applies it to 11 to give the string "11". Cont and runCont are just wrapping and unwrapping functions that we can mostly ignore.

We could have done that without continuations. So what exactly does the Cont monad give us here? Well let's make a 'hole' in the code above:

Whatever integer we place in the hole, the value of test1 will be the result of adding one and applying show. So we can think of that picture as being a function whose argument we shove in the hole. Now Haskell is a functional programming language so we expect that we can somehow reify that function and get our hands on it. That's exactly what the continuation monad Cont does. Let's call the function we're talking about by the name fred. How can we get our hands on it? It's with this piece code:


ex1 = do
a <- return 1
b <- Cont (\fred -> ...)
return $ a+b


The ... is a context in which fred represents "the entire surrounding computation". Such a computaton is known as a "continuation". It's a bit hard to get your head around but the Cont monad allows you to write subexpressions that are able to "capture" the entirety of the code around them, as far as the function provided to runCont. To show that this is the case let's apply fred to the number 10:


> ex2 = do
> a <- return 1
> b <- Cont (\fred -> fred 10)
> return $ a+b

> test2 = runCont ex2 show


The entire computation is applied to 10 and we get "11". Now you know what return does in this monad. But that's a convoluted way of doing things. What other advantages do we get? Well the expression for b can do whatever it wants with fred as long as it returns the same type, ie. a string. So we can write this:


> ex3 = do
> a <- return 1
> b <- Cont (\fred -> "escape")
> return $ a+b

> test3 = runCont ex3 show


fred is completely ignored. The entire computation is thrown away and instead of applying show to a number, we simply return "escape". In other words, we have a mechanism for throwing values out of a computation. So continuations provide, among other things, an exception handling mechanism. But that's curious, because that's exactly what the Maybe monad provides. It looks like we might be able to simulate Maybe this way. But rather than do that, let's do something even more radical.


> ex4 = do
> a <- return 1
> b <- Cont (\fred -> fred 10 ++ fred 20)
> return $ a+b

> test4 = runCont ex4 show


We've used fred twice. We've made the code around our "hole" run twice, each time executing with a different starting value. Continuations allow mere subexpressions to take complete control of the expressions within which they lie. That should remind you of something. It's just like the list monad. The above code is a lot like


> test5 = do
> a <- return 1
> b <- [10,20]
> return $ a+b


So can we emulate the list monad? Well instead of converting our integer to a string at the end we want to convert it to a list. So this will work:


> ex6 = do
> a <- return 1
> b <- Cont (\fred -> fred 10 ++ fred 20)
> return $ a+b

> test6 = runCont ex6 (\x -> [x])


We can avoid those ++ operators by using concat:


> ex7 = do
> a <- return 1
> b <- Cont (\fred -> concat [fred 10,fred 20])
> return $ a+b

> test7 = runCont ex7 (\x -> [x])


But now you may notice we can remove almost every depepndence on the list type to get:


> ex8 = do
> a <- return 1
> b <- Cont (\fred -> [10,20] >>= fred)
> return $ a+b

> test8 = runCont ex8 return


Note, we're using monad related functions, but when we do so we're not using do-notation. We can now do one last thing to tidy this up:


> i x = Cont (\fred -> x >>= fred)
> run m = runCont m return


And now we have something close to do-notation for the list monad at our disposal again:


> test9 = run $ do
> a <- i [1,2]
> b <- i [10,20]
> return $ a+b


I hope you can see how this works. i x says that the continuation should be applied to x, not as an ordinary function, but with >>=. But that's just business as usual for monads. So the above should work for any monad.


> test10 = run $ do
> i $ print "What is your name?"
> name <- i getLine
> i $ print $ "Merry Xmas " ++ name


The Grinch has been foiled and we see that the continuation monad really is the mother of all monads.

There are some interesting consequences of this beyond Haskell. Many languages with support for continuations should be extensible to support monads. In particular, if there is an elegant notation for continuations, there should be one for monads too. This is why I didn't want to talk about the underlying mechanism of the Cont monad. Different languages can implement continuations in different ways. An extreme example is (non-portable) C where you can reify continuations by literally flushing out all registers to memory and grabbing the stack. In fact, I've used this to implement something like the list monad for searching in C. (Just for fun, not for real work.) Scheme has call-with-current-continuation which can be used similarly. And even Python's yield does something a little like reifying a continuation and might be usable this way. (Is that's what's going on here? I haven't read that yet.).

This post was also inspired by this paper by Filinski. I haven't followed the details yet (it's tricky) but the gist is similar. I was actually looking at Filinski's paper because of something I'll mention in my next post.

29 Comments:

Anonymous Anonymous said...

I'm a little confused by ex3. What exactly is fred in this example? The partially applied function '(+) a' i.e. '(+) 1'?

Wednesday, 24 December, 2008  
Blogger augustss said...

I noticed that you don't simulate the state monad. :)

Wednesday, 24 December, 2008  
Blogger sigfpe said...

augustss,

You expecting some kind of failure for state? The code is agnostic about the choice of monad so it'll work for any monad, right?

(runState $ run $ do { a <- i $ get ; i $ modify (+1) ; i $ return a }) 10

Wednesday, 24 December, 2008  
Blogger sigfpe said...

Anonymous,

fred is the same in ex2 and ex3. In both cases it's equal to "show . (+1)".

Inside "<- Cont (\fred -> ...)" fred is the function that does everything up to and including the last argument to the surrounding runCont, which in this case is "show". The stuff in the do-block just adds 1.

Of course in ex3 fred isn't actually used.

You can use the identity id instead of show if you don't want to do anything in particular to the result.

Wednesday, 24 December, 2008  
Blogger augustss said...

Ah, I missed the total cleverness of i. Thanks!

Wednesday, 24 December, 2008  
Anonymous Anonymous said...

I wanted to learn more about continuations for a while. But how do you get Haskell to recognize Control.Monad.Cont? I get a "Could not find module" error when I try to use it.

(And, no, I couldn't find anything useful through Google, though I will happily accept a "Let me google that for you" link :P)

Wednesday, 24 December, 2008  
Blogger sigfpe said...

AliPang,

Try copying this entire post into a file called test.lhs and running that in ghci. If that doesn't work, I wonder if you're missing some libraries. (I only know about ghc.)

Wednesday, 24 December, 2008  
Blogger Cthulhon said...

AliPang: If you're on Gentoo (or perhaps some other *nix with a conservative package manager), you may have to install dev-haskell/mtl (or your *nix's equivalent package name), since GHC does not pull it in as a dependency. Be forewarned, if you are indeed using Gentoo, it may take awhile to compile.

Wednesday, 24 December, 2008  
Anonymous Anonymous said...

I wrote a monads module in scheme few years ago. I wanted to use it for all monads, but Scheme had no namespace or type class. Therefore, the only way is extract the core part of monads (the mother of all monads). This is the major code:

(define bind
(lambda (a b)
(lambda (k)
(a (lambda v ((apply b v) k))))))

(define return
(lambda v
(lambda (k)
(apply k v))))

(define run-IO
(lambda (m)
(m values)))

(define run-State
(lambda (m . s)
(apply (m (lambda r (lambda _ (apply values r)))) s)))

(define State-set
(lambda v
(lambda (k)
(lambda s
(apply (apply k s) v)))))

(define return-List
(lambda l
(lambda (k)
(apply append (map k l)))))

(define run-List
(lambda (m)
(m list)))

I didn't know it is correct or not. After I read you post, I understand I've acturally written a Cont monad and work out other monads with it, same as what you did. You solved my long time question!

Thursday, 25 December, 2008  
Blogger Roly Perera said...

What does all this mean categorically? I haven't yet tried to understand what monad morphisms are (other than that they must be natural transformations that preserve the extra structure of a monad), but does the continuation monad turn out to be initial or terminal in a suitable category?

Thursday, 25 December, 2008  
Blogger Edward Kmett said...

If you look in category-extras there is actually a monad that boxes up this functionality and reflects this idea; the "codensity monad," aka the monad generated by a functor basically represents a CPS transform.

http://hackage.haskell.org/packages/archive/category-extras/0.53.5/doc/html/src/Control-Monad-Codensity.html

Your run corresponds to my lowerCodensity and i corresponds to liftCodensity.

The rest just relies on the fact that:

newtype Codensity m a = Codensity { runCodensity :: forall b. (a -> m b) -> m b }

which can also be read as forall r. ContT (m r) a is a monad regardless of m, (it doesn't even have to be a functor!)

This monad has nice performance characteristics, because it just reflects a CPS transform of the code.

A variation on the presentation is available here:

http://www.haskell.org/haskellwiki/Performance/Monads

Since this represents a CPS transform of the code and is a monad in its own right if the bind operation of the monad is expensive, as in say most free monads, you can change the asymptotic behavior of code that is running in the monad.

Janis Voigtlaender has a paper on the topic, in which you'll recognize the type 'C' that he uses as the Codensity monad above.

http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf

Moreover, if you are looking for a window to understanding Kan extensions, you can view the codensity monad as the right Kan extension of a functor along itself.

Sunday, 28 December, 2008  
Blogger Unknown said...

Great post!

>Many languages with support for continuations should be extensible to support monads
I'd phrase it a little differently: language with support of continuations automatically supports monads with natural syntax.
Perhaps it is worth to mention that one needs delimited control operators to simulate monadic do-notation (in case of Control.Monad.Cont the 'runCont' function is a control delimiter).

Tuesday, 30 December, 2008  
Blogger sigfpe said...

Roly,

> What does all this mean categorically?

I had the same thought as you - Cont must be terminal or final in some category. But I haven't figured out what category that is.

Friday, 02 January, 2009  
Blogger Edward Kmett said...

sigfpe/rory:

As a sketch for how 'ContT is terminal':

If you discard the information about the return value's type through quantification (using a forall, or less safely just using the current continuation in a 'very limited' manner) then you can view ContT as a right Kan extension of a functor F along itself. That can be viewed as a limit taken pointwise over a comma category - just invert the colimit example in the wikipedia article on Kan extensions to take a limit of Ran instead a colimit of Lan. That limit is a terminal object in a category of cones.

ContT is slightly larger than this, in that you CAN abuse the current continuation. That said, to define a codensity monad and lift/lower monadic actions into it as you have done, you do not use that extra functionality.

The fact that you can lift any monad into it (by CPS transformation) is just a consequence of the existence of the codensity monad, ContT is actually a bit bigger than it needs to be.

This is all just another way to say that a CPS transformation can always be applied.

And you can take away from this, somewhat tongue in cheek, that continuations are slightly more complicated than they need to be to do the job. ;)

Monday, 05 January, 2009  
Blogger A Breaking Change said...

you lost me a bit at "ex8". I think what I see is that [10,20] >>= fred is a bind in the LIST monad, and not in the continuation monad, as is the final "return" in "runCont ex8 return." I think "fred" has type "x->[x]" so [10,20]>>=fred means 'bind [10,20] to x, build [[10,20]] and flatten one level, producing [10,20]", which, if memory serves, is what the >>= of the list monad does. Have I got it?

Sunday, 19 April, 2009  
Blogger sigfpe said...

Secret Agent for the Dumb,

>>= basically applies a function to each element of a list, and then flattens the entire result. But I think you got that already.

Thursday, 03 December, 2009  
Blogger Tyr said...

The code is broken now. :(

Tuesday, 22 November, 2011  
Blogger sigfpe said...

Tyr,

Try replacing occurrences of the constructor "Cont" with the function "cont". After this I can load the .lhs file in ghci and it all works. (I'm using version 2011.2.0.1 of the Haskell Platform.)

(This was posted by 'anonymous' but I accidentally deleted it so this is a repost by me.)

Saturday, 03 December, 2011  
Anonymous michaelt said...

I was trying to figure this out again. Here is the code as it stood in 2008 running on Hugs: http://codepad.org/iJyF916i Here are literate and delit-ed versions presupposing the new `type Cont a = ContT a Identity` as sigfpe suggested

Friday, 18 May, 2012  
Blogger Sean Kanaley said...

At first it seems amazing that Cont can do anything, but an almost analogous statement shows it's a ruse:

"The identity function is the mother of all functions." -- one can simulate (+3) with id (+3).

That statement is actually closer to saying IdentityT is the mother of all monads, e.g. IdentityT (State Int) = State Int. But ContT is just CPS-ified IdentityT. The Cont monad doesn't *do* anything except for what it's told to do, similar to id.

For example, when you simulated the list monad you did so by hard-coding in the implementation of list's bind then wrapping it in Cont, just like (+3) can be wrapped in id. All Cont does is defer computation, so the actual computation that is deferred is what truly defines it. In this sense the statement that Cont can do anything suddenly seems vacuous! It can do anything because it does nothing except for the parameter/inlined code telling it exactly what to do! We can also say an empty .hs file is the mother of all Haskell programs.

Wednesday, 12 March, 2014  
Blogger sigfpe said...

@Sean,

Suppose that Haskell do-notation only supported the Identity type, not the full Monad type class. How would you leverage it to get something as close as possible to the original do-notation that works with any Monad.

Wednesday, 12 March, 2014  
Blogger Sean Kanaley said...

I believe what you are getting at is that Identity has no input by which to parameterize its behavior. It can only ever give effectively pure code, and IdentityT can only give back the contained monad, but Cont actually lifts pure code into a monad through the hook provided by the continuation function. My analogy with id would have been better if I said id converts assembler into a Haskell function, e.g. id (mov bx,3; add ax,bx; etc.) where id is the context that builds a function (but otherwise does not affect the provided behavior), assigns the input parameter to ax, etc. Cont and id would then both set up a surrounding context by which more primitive operations define the container type.

I would think this idea of containing lower stuff with nearly-id-higher stuff (contified stuff) would hold in general, and one could claim that continuations are the mother of all everythings. Or is there some type class where this transformation fails?

Friday, 14 March, 2014  
Blogger sigfpe said...

> one could claim that continuations are the mother of all everythings

Sure. Every computation can be seen as some stuff being provided to a continuation which then runs with it. But I'm talking specifically about monads. Among the collection of monads the continuation monad provides a universal monad in which all others can be embedded. The function 'i' is in fact a monad morphism so this gives a principled way to use continuations to perform the function of any monad rather than simply saying "I can do anything because at the end of the day code is all just a bunch of machine code".

This isn't just a vacuous statement. As I mentioned, given any language with a syntax for continuations you have the possibility of reusing that notation for monads. For example Python has linear continuations (via generators) so you can use this as a syntax for any of the 'linear' monads (like Identity, Maybe and Writer I think).

Friday, 14 March, 2014  
Blogger Sean Kanaley said...

I see, the syntax reuse is a nice effect. In regard to "i", I tried defining a comparable function for arrows to reuse arrow syntax, but it seems impossible (no way to pass the result of x to the continuation). This is strange because e.g. put/get are simple to define for the Cont Arrow simulating the State Arrow, which then can use arrow syntax just fine. Syntax reuse is thus not limited to monads, but the "i" function might be? (I'm not a theory expert.)

Friday, 14 March, 2014  
Blogger Edward Kmett said...

The State arrow factors into a monad.

(a,s) -> (b,s) is isomorphic to a -> s -> (b, s) whi
ich is a -> State s b

That s why you can define it for State, but not every arrow factors that way.

Friday, 14 March, 2014  
Blogger Edward Kmett said...

The State arrow factors into a monad.

(a,s) -> (b,s) is isomorphic to a -> s -> (b, s) whi
ich is a -> State s b

That s why you can define it for State, but not every arrow factors that way.

Friday, 14 March, 2014  
Blogger D said...

Trying to wrap my head around this... with ex7, would you be able to get a way with

> ex7 = do
>   a <- return 1
>   b <- Cont (\fred -> fred 10 `mplus` fred 20)
>   return $ a+b

to make it agnostic to any implementation MonadPlus?

Thursday, 10 September, 2015  
Blogger Philip Wadler said...

Dan, Isn't this post more clearly explained by the construction in Section 3.3 of Wadler (1992), which shows how to embed any arbitrary monad into the continuation monad?

Philip Wadler, The Essence of Functional Programming, POPL 1992.

Friday, 19 August, 2016  
Blogger Unknown said...

Why does everyone feel the need to make the categorical semantics here way more complex then it needs to be?

If you read further into Andrzej Filinski's work, you'd come across the paper "Declaritive Continuations: an Investigation of Duality in Programming Language Semantics". In it, Filinski describes a symmetric lambda calculus wherein continuations are given a dual semantics.

The symmetric lambda calculus is the internal language to a bi-cartesian bi-closed category, which is a category which has a terminal object (1), products (⊗), exponential map (⇒), initial object (0), coproduct/sums (⊕), and crucially, co-expontials (⇐), also sometimes called subtraction.

Under this identification, defining do-notation is now quite simple, it's the co-evaluation map:
do:[y←x] := ((y ⇐ x)⊕x)

Saturday, 07 January, 2017  

Post a Comment

<< Home