From this thread (Control.Monad.Cont fun, 2005), Tomasz Zielonka introduced a function (commented in a clear and nice manner by Thomas Jäger). Tomasz takes the argument (a function) of a callCC body and returns it for later usage with the following two definitions:
import Control.Monad.Cont
...
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))
Those are also mentioned in Haskellwiki. Using them, you can resemble goto semantics in haskell which looks really cool:
import Control.Monad.Cont
getCC' :: MonadCont m => a -> m (a, a -> m b)
getCC' x0 = callCC (\c -> let f x = c (x, f) in return (x0, f))
main :: IO ()
main = (`runContT` return) $ do
(x, loopBack) <- getCC' 0
lift (print x)
when (x < 10) (loopBack (x + 1))
lift (putStrLn "finish")
This prints the numbers 0 to 10.
Here comes the interesting point. I used this together with the Writer Monad to solve a certain problem. My code looks like the following:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, UndecidableInstances #-}
import Control.Monad.Cont
import Control.Monad.Writer
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))
-- a simple monad transformer stack involving MonadCont and MonadWriter
type APP= WriterT [String] (ContT () IO)
runAPP :: APP a -> IO ()
runAPP a= runContT (runWriterT a) process
where process (_,w)= do
putStrLn $ unlines w
return ()
driver :: Int -> APP ()
driver k = do
tell [ "The quick brown fox ..." ]
(x,loop) <- getCC' 0
collect x
when (x<k) $ loop (x+1)
collect :: Int -> APP ()
collect n= tell [ (show n) ]
main :: IO ()
main = do
runAPP $ driver 4
When you compile and run this code, the output is:
The quick brown fox ...
4
The numbers zero to three are swallowed somewhere in the profound darkness of this example.
Now, in "Real World Haskell" O'Sullivan, Goerzen and Stewart states
"Stacking monad transformers is analogous to composing functions. If we change the order in which we apply functions and then get different results, we won't be suprised. So it is with monad transformers, too." (Real World Haskell, 2008, P. 442)
I came up with the idea to swap the transformers above:
--replace in the above example
type APP= ContT () (WriterT [String] IO)
...
runAPP a = do
(_,w) <- runWriterT $ runContT a (return . const ())
putStrLn $ unlines w
However, this won't compile because there is no instance definition for MonadWriter in Control.Monad.Cont (which is why I recently asked this question.)
We add an instance leaving listen and pass undefined:
instance (MonadWriter w m) => MonadWriter w (ContT r m) where
tell = lift . tell
listen = undefined
pass = undefined
Add those lines, compile and run. All numbers are printed.
What has happened in the previous example?
Here's a somewhat informal answer, but hopefully useful. getCC'
returns a continuation to the current point of execution; you can think of it as saving a stack frame. The continuation returned by getCC'
has not only ContT
's state at the point of the call, but also the state of any monad above ContT
on the stack. When you restore that state by calling the continuation, all of the monads built above ContT
return to their state at the point of the getCC'
call.
In the first example you use type APP= WriterT [String] (ContT () IO)
, with IO
as the base monad, then ContT
, and finally WriterT
. So when you call loop
, the state of the writer is unwound to what it was at the getCC'
call because the writer is above ContT
on the monad stack. When you switch ContT
and WriterT
, now the continuation only unwinds the ContT
monad because it's higher than the writer.
ContT
isn't the only monad transformer that can cause issues like this. Here's an example of a similar situation with ErrorT
func :: Int -> WriterT [String] (ErrorT String IO) Int
func x = do
liftIO $ print "start loop"
tell [show x]
if x < 4 then func (x+1)
else throwError "aborted..."
*Main> runErrorT $ runWriterT $ func 0
"start loop"
"start loop"
"start loop"
"start loop"
"start loop"
Left "aborted..."
Even though the writer monad was being told values, they're all discarded when the inner ErrorT
monad is run. But if we switch the order of the transformers:
switch :: Int -> ErrorT String (WriterT [String] IO) ()
switch x = do
liftIO $ print "start loop"
tell [show x]
if x < 4 then switch (x+1)
else throwError "aborted..."
*Main> runWriterT $ runErrorT $ switch 0
"start loop"
"start loop"
"start loop"
"start loop"
"start loop"
(Left "aborted...",["0","1","2","3","4"])
Here the internal state of the writer monad is preserved, because it's lower than ErrorT
on the monad stack. The big difference between ErrorT
and ContT
is that ErrorT
's type makes it clear that any partial computations will be discarded if an error is thrown.
It's definitely simpler to reason about ContT
when it's at the top of the stack, but it is on occasion useful to be able to unwind a monad to a known point. A type of transaction could be implemented in this manner, for example.
I spent some time tracing this in the λ calculus. It generated pages and pages of derivations that I won't attempt to reproduce here, but I did gain a little insight on how the monad stack works. Your type expands as follows:
type APP a = WriterT [String] (ContT () IO) a
= ContT () IO (a,[String])
= ((a,[String]) -> IO()) -> IO()
You can similarly expand out Writer's return
, >>=
, and tell
, along with Cont's return
, >>=
, and callCC
. Tracing it is extremely tedious though.
The effect of calling loop
in the driver is to abandon the normal continuation and instead return, again, from the call to getCC'
. That abandoned continuation contained the code that would have added the current x
to the list. So instead, we repeat the loop, but now x
is the next number, and only when we hit the last number (and thus don't abandon the continuation) do we piece together the list from ["The quick brown fox"]
and ["4"]
.
Just as “Real World Haskell” emphasizes that the IO monad needs to stay on the bottom of the stack, it also seems important that the continuation monad stays on top.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With