[Haskell-beginners] Suspend/resume computation using Cont monad and callCC

Dmitriy Matrosov sgf.dma at gmail.com
Tue Mar 12 11:50:17 CET 2013


Hi.

I have two functions f and g, and i want them to execute in following
order: first function f runs, then suspends and passes control to
function g. Function g runs, then suspends and "unpauses" function f.
Function f finishes and passes control to function g, which also
finishes. Here is illustration ('o' means start of function, dot means
suspend and pass control to other function, 'x' means end of function):

	    f   g
	    o
      f-1   |
	    v
	    .-->o
		|   g-1
		v
	    .<--.
	    |
      f-2   v
	    x-->.
		|   g-2
		v
     <----------x
  (to caller)

I want to implement this using Cont monad and callCC. And here is my
implementation:


    import Data.Monoid
    import Control.Monad.Cont
    import Control.Monad.Writer


    type M r            = Cont r

    fM :: M r [String]
    fM                  = do
        let xs' = "I'm in f-1" : []
        (ys, k') <- callCC (gM xs')
        let ys' = "I'm in f-2" : ys
        zs <- k' ys'
        let zs' = "I'm in f-3" : zs
        return zs'

    gM :: [String]
          -> (([String], [String] -> M r [String]) -> M r [String])
          -> M r ([String], [String] -> M r [String])
    gM xs k             = do
        let xs' = "I'm in g-1" : xs
        ys <- callCC (curry k xs')
        let ys' = "I'm in g-2" : ys
        return (ys', \_ -> return ys')

    type T r            = ContT r (Writer String)

    fT :: T r ()
    fT                  = do
        lift $ tell "I'm in f-1\n"
        k' <- callCC gT
        lift $ tell "I'm in f-2\n"
        k' undefined
        lift $ tell "I'm in f-3\n"

    gT :: ((() -> T r ()) -> T r ()) -> T r (() -> T r ())
    gT k                = do
        lift $ tell "I'm in g-1\n"
        callCC k
        lift $ tell "I'm in g-2\n"
        return (\_ -> return ())

First pair (fM and gM) uses monad result to track execution order,
second pair (fT and gT) uses Writer monad. But the tracks produced by
these pairs differ:

    *Main> runCont fM id
    ["I'm in f-3","I'm in g-2","I'm in f-2","I'm in g-1","I'm in f-1"]
    *Main> putStr . snd . runWriter . flip runContT return $ fT
    I'm in f-1
    I'm in g-1
    I'm in f-2
    I'm in g-2
    I'm in f-2      <----- Why am i here?
    I'm in f-3

fM/gM pair produces exactly the track, which i expect (see illustration
above, though 'f-3' section does not shown there). But fT/gT pair after
'g-2' section returns to "before f-2" point in function f. And i don't
understand why.

Thus, my question is why does fT/gT work so? And why do results from these
pairs differ?

--
    Dmitriy Matrosov



More information about the Beginners mailing list