[Haskell-cafe] Re: Control.Monad.Cont fun
oleg at pobox.com
oleg at pobox.com
Thu Jul 7 21:02:36 EDT 2005
Tomasz Zielonka wrote:
> Some time ago I wanted to return the escape continuation out of the
> callCC block, like this:
> getCC = callCC (\c -> return c)
patterns like this are characteristic of shift/reset
-- From http://www.haskell.org/hawiki/MonadCont
reset :: (Monad m) => ContT a m a -> ContT r m a
reset e = ContT $ \k -> runContT e return >>= k
shift :: (Monad m) =>
((a -> ContT r m b) -> ContT b m b)
-> ContT b m a
shift e = ContT $ \k ->
runContT (e $ \v -> ContT $ \c -> k v >>= c) return
with them, we can implement the same tests, in a slightly de-sugared
way, for clarity:
> newtype H r m = H (H r m -> ContT r m r)
> unH (H x) = x
>
> -- prints "hello!" in an endless loop
> test :: IO ()
> test = (`runContT` return) $ reset (do
> jump <- shift (\f -> f (H f))
> lift (putStrLn "hello!")
> unH jump jump)
> newtype H' r m a = H' ((a,H' r m a) -> ContT r m ())
> unH' (H' x) = x
>
> -- prints integers from 0 to 10, then prints finish and ends
> test' :: IO ()
> test' = (`runContT` return) $
> do
> reset (do
> (x, jumpWith) <- (\x -> shift (\f -> f (x,(H' f)))) 0
> lift (print x)
> when (x < 10) (unH' jumpWith ((x + 1),jumpWith)))
> lift (putStrLn "finish")
Delimited continuations are really cool.
The lack of the answer-type polymorphism in ContT will come to bite us in
the end: we can't use reset several times in differently-typed
contexts (which often means that we can use reset only once in our
program). The CC monad transformer (derived from the CC library by
Sabry, Dybvig, Peyton-Jones), freely available from
http://pobox.com/~oleg/ftp/packages/LogicT.tar.gz
is free from that drawback.
BTW, with that monad transformer, the example looks as follows (again,
in a de-sugared way, for clarity)
> import CC_2CPST
> newtype H'' r m a = H'' (CC r m (a,H'' r m a) -> CC r m ())
> unH'' (H'' x) = x
> test'' :: IO ()
> test'' = runCC (
> do
> p <- newPrompt
> pushPrompt p (
> do
> (x, jumpWith) <- (\x -> shiftP p (\f -> f (return (x,(H'' f))))) 0
> lift (print x)
> when (x < 10) (unH'' jumpWith (return ((x + 1),jumpWith))))
> lift (putStrLn "finish"))
>
> shiftP p f = letSubCont p $ \sk ->
> pushPrompt p (f (\c ->
> pushPrompt p (pushSubCont sk c)))
More information about the Haskell-Cafe
mailing list