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?
ContT
andErrorT
should be on top of the monad stack, sort of likeIO
should be on the bottom. I know very little about monads, and less aboutContT
andErrorT
, but this nevertheless seems to ring true to me. This might be good material for an academic paper or book or something. – Dan BurtonErrorT
typically goes on the bottom, directly aboveIO
. This is because if there's an error in the computation, any values from other monads (esp. state or writer) are partial and generally not informative. Despite that, your suggestion is somewhat compelling, I'd like to see more in this area as well. – John L