Understanding Haskell callCC examples

大兔子大兔子 提交于 2019-12-06 03:33:12

问题


I am having trouble understanding the answers to a previous question. I'm hoping that an explanation of the following will clarify things. The following example comes from fpcomplete

import Control.Monad.Trans.Class
import Control.Monad.Trans.Cont

main = flip runContT return $ do
    lift $ putStrLn "alpha"
    (k, num) <- callCC $ \k -> let f x = k (f, x)
                               in return (f, 0)
    lift $ putStrLn "beta"
    lift $ putStrLn "gamma"
    if num < 5
        then k (num + 1) >> return ()
        else lift $ print num

The output is

alpha
beta
gamma
beta
gamma
beta
gamma
beta
gamma
beta
gamma
beta
gamma
5

I think I understand how this example works, but why is it necessary to have a let expression in the callCC to "return" the continuation so that it can be used later on. So I tried to directly return the continuation by taking the following simpler example and modifying it.

import Control.Monad.Trans.Class
import Control.Monad.Trans.Cont

main = flip runContT return $ do
    lift $ putStrLn "alpha"
    callCC $ \k -> do
      k ()
      lift $ putStrLn "uh oh..."
    lift $ putStrLn "beta"
    lift $ putStrLn "gamma"

This prints

alpha
beta
gamma

And I modified it to the following

import Control.Monad.Trans.Class
import Control.Monad.Trans.Cont

main = flip runContT return $ do
    lift $ putStrLn "alpha"
    f <- callCC $ \k -> do
      lift $ putStrLn "uh oh..."
      return k
    lift $ putStrLn "beta"
    lift $ putStrLn "gamma"

The idea being that the continuation would get returned as f and be unused in this test example which I would expect to print

uh oh...
beta
gamma

But this example doesn't compile, why can't this be done?

Edit: Consider the analgous example in Scheme. As far as I know Scheme wouldn't have a problem, is that correct?, but why?.


回答1:


Looking at your examples in reverse order.

The last example does not typecheck due to an infinite type. Looking at the type of callCC, it is ((a -> ContT r m b) -> ContT r m a) -> ContT r m a. If we try to return the continuation we return something of type ContT r m (a -> ContT r m b). This means we get the type equality constraint a ~ (a -> ContT r m b), which means a has to be an infinite type. Haskell does not allow these (in general, for good reason - as far as I can tell the infinite type here would be something along the lines of, supply it an infinite order function as an argument).

You don't mention whether there's anything you're confused about in the second example, but. The reason that it does not print "uh oh..." is because the ContT action produced by k (), unlike many ContT actions does not use the following computation. This is the difference between the continuations and just normal functions which return ContT actions (disclaimer, any function could return a ContT action like this, but in general). So, when you follow the k () up with a print, or anything else, it is irrelevant, because the k () just discards the following actions.

So, the first example. The let binding here is actually only used to mess around with the parameters to k. But by doing so we avoid an infinite type. Effectively, we do some recursion in the let binding which is related to the infinite type we got before. f is a little bit like a version of the continuation with the recursion already done.

The type of this lambda we pass to callCC is Num n => ((n -> ContT r m b, n) -> ContT r m b) -> ContT r m (n -> ContT r m b, n). This does not have the same infinite type problem that your last example has, because we messed around with the parameters. You can perform a similar trick without adding the extra parameter by using let bindings in other ways. For example:

recur :: Monad m => ContT r m (ContT r m ())
recur = callCC $ \k -> let r = k r in r >> return r

This probably wasn't a terribly well explained answer, but the basic idea is that returning the continuation directly will create an infinite type problem. By using a let binding to create some recursion inside the lambda you pass to callCC, you can avoid this.




回答2:


As the others have written the last example does not typecheck due to an infinite type.

@augustss proposed another way of solving this problem:

You can also make a newtype to wrap the infinite (equi-)recursive type into a (iso-)recursive newtype. – augustss Dec 12 '13 at 12:50

Here's my take at it:

import Control.Monad.Trans.Cont
import Control.Monad.Trans.Class

data Mu t = In { out :: t (Mu t) }

newtype C' b a = C' { unC' :: a -> b }
type C b = Mu (C' b)

unfold = unC' . out
fold = In . C'

setjmp = callCC $ (\c -> return $ fold c)
jump l = unfold l l

test :: ContT () IO ()
test = do
    lift $ putStrLn "Start"
    l <- setjmp
    lift $ putStrLn "x"
    jump l

main = runContT test return

I think this is what @augustss had in mind.




回答3:


The example executes in the ContT () IO monad, the Monad allowing continuations that result in () and some lifted IO.

type ExM a = ContT () IO a

ContT can be an incredibly confusing monad to work in, but I've found that Haskell's equational reasoning is a powerful tool for disentangling it. The remainder of this answer examines the original example in several steps, each powered by syntactic transforms and pure renamings.

So, let's first examine the type of the callCC part—it's ultimately the heart of this entire piece of code. That chunk is responsible for generating a strange kind of tuple as its monadic value.

type ContAndPrev = (Int -> ExM (), Int)

getContAndPrev :: ExM ContAndPrev
getContAndPrev = callCC $ \k -> let f x = k (f, x) 
                                in return (f, 0)

This can be made a little bit more familiar by sectioning it with (>>=), which is exactly how it would be used in a real context—any do-block desugaring will create the (>>=) for us eventually.

withContAndPrev :: (ContAndPrev -> ExM ()) -> ExM ()
withContAndPrev go = getContAndPrev >>= go

and finally we can examine that it actually looks like in the call site. To be more clear, I'll desugar the original example a little bit

flip runContT return $ do
  lift (putStrLn "alpha")
  withContAndPrev $ \(k, num) -> do
    lift $ putStrLn "beta"
    lift $ putStrLn "gamma"
    if num < 5
      then k (num + 1) >> return ()
      else lift $ print num

Notice that this is a purely syntactic transformation. The code is identical to the original example, but it highlights the existence of this indented block under withContAndPrev. This is the secret to understanding Haskell callCC---withContAndPrev is given access to the entire "rest of the do block" which it gets to choose how to use.

Let's ignore the actual implementation of withContAndPrev and just see if we can create the behavior we saw in running the example. It's fairly tricky, but what we want to do is pass into the block the ability to call itself. Haskell being as lazy and recursive as it is, we can write that directly.

withContAndPrev' :: (ContAndPrev -> ExM ()) -> ExM ()
withContAndPrev' = go 0 where 
  go n next = next (\i -> go i next, n)

This is still something of a recursive headache, but it might be easier to see how it works. We're taking the remainder of the do block and creating a looping construct called go. We pass into the block a function that calls our looper, go, with a new integer argument and returns the prior one.

We can begin to unroll this code a bit by making a few more syntactic changes to the original code.

maybeCont :: ContAndPrev -> ExM ()
maybeCont k n | n < 5     = k (num + 1)
              | otherwise = lift (print n)

bg :: ExM ()
bg = lift $ putStrLn "beta" >> putStrLn "gamma"

flip runContT return $ do
  lift (putStrLn "alpha")
  withContAndPrev' $ \(k, num) -> bg >> maybeCont k num

And now we can examine what this looks like when betaGam >> maybeCont k num gets passed into withContAndPrev.

let go n next = next (\i -> go i next, n)
    next      = \(k, num) -> bg >> maybeCont k num
in
  go 0 next
  (\(k, num) -> betaGam >> maybeCont k num) (\i -> go i next, 0)
  bg >> maybeCont (\i -> go i next) 0
  bg >> (\(k, num) -> betaGam >> maybeCont k num) (\i -> go i next, 1)
  bg >> bg >> maybeCont (\i -> go i next) 1
  bg >> bg >> (\(k, num) -> betaGam >> maybeCont k num) (\i -> go i next, 2)
  bg >> bg >> bg >> maybeCont (\i -> go i next) 2
  bg >> bg >> bg >> bg >> maybeCont (\i -> go i next) 3
  bg >> bg >> bg >> bg >> bg >> maybeCont (\i -> go i next) 4
  bg >> bg >> bg >> bg >> bg >> bg >> maybeCont (\i -> go i next) 5
  bg >> bg >> bg >> bg >> bg >> bg >> lift (print 5)

So clearly our fake implementation recreates the behavior of the original loop. It might be slightly more clear how our fake behavior achieves that by tying a recursive knot using the "rest of the do block" which it receives as an argument.

Armed with this knowledge, we can take a closer look at callCC. We'll again profit by initially examining it in its pre-bound form. It's extremely simple, if weird, in this form.

withCC gen block = callCC gen >>= block
withCC gen block = block (gen block)

In other words, we use the argument to callCC, gen, to generate the return value of callCC, but we pass into gen the very continuation block that we end up applying the value to. It's recursively trippy, but denotationally clear—callCC is truly "call this block with the current continuation".

withCC (\k -> let f x = k (f, x)
              in  return (f, 0)) next
next (let f x = next (f, x) in return (f, 0))

The actual implementation details of callCC are a bit more challenging since they require that we find a way to define callCC from the semantics of (callCC >>=) but that's mostly ignorable. At the end of the day, we profit from the fact that do blocks are written so that each line gets the remainder of the block bound to it with (>>=) which provides a natural notion of continuation immediately.




回答4:


why is it necessary to have a let expression in the callCC to "return" the continuation so that it can be used later on

Thats the exact use of continuation, i.e capture the current execution context and then later use this capture continuation to jump back to that execution context.

It seems that you are confused by the function name callCC, which may be indicating to you that it is calling a continuation BUT actually it is creating a continuation.



来源:https://stackoverflow.com/questions/20536700/understanding-haskell-callcc-examples

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!