Does anybody have a simple example of using continuation Monad?

I'm struggling with this example: http://www.nomaware.com/monads/html/contmonad.html#example After looking at it for the fourth time I got much more.. but still not enough.. because there are so much new things (when beeing translated into some kind of condition ?> thentodo :> elsetodo which is using ThenElse .... It wouldn't be any problem if the next example wasn't using continuation, too.. and that's about combining monads which is important, isn't it? At the tutorial there was mentioned that continuation monads are used for continuation passing style which I've looked up in wikipedia meaning something like splitting a task into different parts beeing executed delayed (for example because of user interaction filling a web form?) I think one simple example like ((+1).(\x->x**2)) in continuation style would make me understand a lot more.. Marc

On 12/01/06, Marc Weber
I'm struggling with this example: http://www.nomaware.com/monads/html/contmonad.html#example After looking at it for the fourth time I got much more.. but still not enough..
because there are so much new things (when beeing translated into some kind of condition ?> thentodo :> elsetodo which is using ThenElse ....
It wouldn't be any problem if the next example wasn't using continuation, too.. and that's about combining monads which is important, isn't it?
At the tutorial there was mentioned that continuation monads are used for continuation passing style which I've looked up in wikipedia meaning something like splitting a task into different parts beeing executed delayed (for example because of user interaction filling a web form?)
I think one simple example like ((+1).(\x->x**2)) in continuation style would make me understand a lot more..
Marc
Yeah, that's probably what bothers me most about All About Monads, as it's otherwise quite a good tutorial. Continuations are a strange concept, and not exactly the first thing that beginners need to see. The continuation monad/transformer has its place, but it's rarely needed, and when abused, it just results in an unreadable mess. The basic idea about the continuation monad is that the entire computation you are defining is parametrised on a function which will take its result and continue to operate on it (the 'future'). The computation is built up in this way -- at each stage, we extend the computation by providing another piece of the future, while still leaving the computation as a whole parametrised on it. Normally we'd be forced to manage these futures by having explicit parameters for them and such, but the monad machinery hides all of this so that you don't have to worry so much about it. If you don't ever make use of the extra feature that you can get a handle on the future, you can use it just like the identity monad: addOne x = return (x+1) square x = return (x**2) f x = do y <- addOne x; square y With explicit continuations, this would look something like: addOne x k = k (x + 1) square x k = k (x ** 2) f x k = addOne x (\v -> square v k) Now, this seems like an awkward way to handle things as we're not making any use of the fact that at each stage, we have a handle to the future which can be used multiple times, passed into other functions, etc. The Cont monad gives one primitive for capturing the current continuation and passing it into a computation, called callCC. callCC :: ((a -> Cont b) -> Cont a) -> Cont a This type requires some study to understand at first, but essentially, callCC takes a function from a future (a -> Cont b) to a new computation (Cont a), and passes it the current future (which is accessible due to the funny way in which we're parametrising our computations). In terms of callCC, we can write other, more convenient ways to manipulate futures. The following is due to Tomasz Zielonka [1]: getCC :: MonadCont m => m (m a) getCC = callCC (\c -> let x = c x in return x) getCC' :: MonadCont m => a -> m (a, a -> m b) getCC' x0 = callCC (\c -> let f x = c (x, f) in return (x0, f)) getCC will get the current continuation explicitly as a computation which can be executed. This essentially gives us a 'goto-label' at that point in the computation, and executing it will jump back. This isn't terribly useful in plain Cont, except to land us in an infinite loop, but over a state monad, or IO, we can cause side-effect havoc, observe the state, and decide whether to return to the goto-label or not. Stealing an example from Tomasz' original message: -- prints "hello!" in an endless loop test :: IO () test = (`runContT` return) $ do jump <- getCC lift $ putStrLn "hello!" jump getCC' is similar, but actually allows an additional parameter to be sent back. The parameter to getCC' is just the initial value. Here's a simplistic implementation of mod by repeated addition/subtraction which prints intermediate results as it goes, in the ContT transformed IO monad. x `modulo` m = (`runContT` return) $ do (u, jump) <- getCC' x lift $ print u case u of _ | u < 0 -> jump (u + m) | u >= m -> jump (u - m) | otherwise -> return u - Cale [1] http://www.haskell.org/pipermail/haskell-cafe/2005-July/010623.html

Am Freitag, 13. Januar 2006 01:31 schrieb Cale Gibbard:
On 12/01/06, Marc Weber
wrote: I think one simple example like ((+1).(\x->x**2)) in continuation style would make me understand a lot more..
Marc
The basic idea about the continuation monad is that the entire computation you are defining is parametrised on a function which will take its result and continue to operate on it (the 'future'). The computation is built up in this way -- at each stage, we extend the computation by providing another piece of the future, while still leaving the computation as a whole parametrised on it.
Normally we'd be forced to manage these futures by having explicit parameters for them and such, but the monad machinery hides all of this so that you don't have to worry so much about it. If you don't ever make use of the extra feature that you can get a handle on the future, you can use it just like the identity monad:
addOne x = return (x+1) square x = return (x**2) f x = do y <- addOne x; square y
With explicit continuations, this would look something like:
addOne x k = k (x + 1) square x k = k (x ** 2) f x k = addOne x (\v -> square v k)
Now, this seems like an awkward way to handle things as we're not making any use of the fact that at each stage, we have a handle to the future which can be used multiple times, passed into other functions, etc.
The Cont monad gives one primitive for capturing the current continuation and passing it into a computation, called callCC.
callCC :: ((a -> Cont b) -> Cont a) -> Cont a
This type requires some study to understand at first, but essentially, callCC takes a function from a future (a -> Cont b) to a new computation (Cont a), and passes it the current future (which is accessible due to the funny way in which we're parametrising our computations).
In terms of callCC, we can write other, more convenient ways to manipulate futures. The following is due to Tomasz Zielonka [1]:
getCC :: MonadCont m => m (m a) getCC = callCC (\c -> let x = c x in return x)
getCC' :: MonadCont m => a -> m (a, a -> m b) getCC' x0 = callCC (\c -> let f x = c (x, f) in return (x0, f))
getCC will get the current continuation explicitly as a computation which can be executed. This essentially gives us a 'goto-label' at that point in the computation, and executing it will jump back. This isn't terribly useful in plain Cont, except to land us in an infinite loop, but over a state monad, or IO, we can cause side-effect havoc, observe the state, and decide whether to return to the goto-label or not.
Stealing an example from Tomasz' original message:
-- prints "hello!" in an endless loop test :: IO () test = (`runContT` return) $ do jump <- getCC lift $ putStrLn "hello!" jump
getCC' is similar, but actually allows an additional parameter to be sent back. The parameter to getCC' is just the initial value. Here's a simplistic implementation of mod by repeated addition/subtraction which prints intermediate results as it goes, in the ContT transformed IO monad.
x `modulo` m = (`runContT` return) $ do (u, jump) <- getCC' x lift $ print u case u of _ | u < 0 -> jump (u + m)
| u >= m -> jump (u - m) | otherwise -> return u
- Cale
[1] http://www.haskell.org/pipermail/haskell-cafe/2005-July/010623.html
This helps, but not enough for me, unfortunately. Could someone give or point to an example of medium complexity? Something to bridge the gap between a CPS-factorial and ReadP, preferably with an explanation why CPS is used ? Cheers, Daniel
participants (3)
-
Cale Gibbard
-
Daniel Fischer
-
Marc Weber