How to abort a computation within Continuation Monad?

Hi, I have been using plain non-monadic CPS for a while in my web-browser related stuff. Now I am tempted to switch from plain CPS to syntactically sweetened monadic style based on Continuation Monad, but I feel stuck with one important issue that I need an advice on. In plain CPS, I may write: type CPS x y = (y -> x) -> x a :: x a = f1 x $ \r -> case r of foo1 -> bar -- of type x foo2 -> f2 r $ \p -> ... -- something finally evaluating to a value of type x So, if at any time I return a value of a final type (x) instead of doing something with given continuation, I abort/suspend the whole computation. This can happen at any function call depth. I can also save the continuation reference in some persistent place, to resume the remainder of computation later. Now, I am trying to do the same with a Continuation Monad. But does anything similar exist in this monad? callCC is not exactly what I need because it only helps abort the inner computation, and what is returned, is a monadic value, not a final value. Besides, callCC defines a name of the function corresponding to the current continuation, and in order to use it, this name should be visible. If I have callCC $ \exit -> do foo ... I cannot jump to `exit' from within foo unless `exit' is given to foo as an argument. Any suggestions? Thanks. -- Dimitry Golubovsky Anywhere on the Web

On Tue, 2007-11-20 at 00:18 -0500, Dimitry Golubovsky wrote:
Hi,
I have been using plain non-monadic CPS for a while in my web-browser related stuff. Now I am tempted to switch from plain CPS to syntactically sweetened monadic style based on Continuation Monad, but I feel stuck with one important issue that I need an advice on.
In plain CPS, I may write:
type CPS x y = (y -> x) -> x
a :: x
a = f1 x $ \r -> case r of foo1 -> bar -- of type x foo2 -> f2 r $ \p -> ... -- something finally evaluating to a value of type x
So, if at any time I return a value of a final type (x) instead of doing something with given continuation, I abort/suspend the whole computation. This can happen at any function call depth. I can also save the continuation reference in some persistent place, to resume the remainder of computation later.
Now, I am trying to do the same with a Continuation Monad. But does anything similar exist in this monad? callCC is not exactly what I need because it only helps abort the inner computation, and what is returned, is a monadic value, not a final value. Besides, callCC defines a name of the function corresponding to the current continuation, and in order to use it, this name should be visible.
If I have
callCC $ \exit -> do foo ...
I cannot jump to `exit' from within foo unless `exit' is given to foo as an argument.
Any suggestions?
The best approach is probably to write a small variant of callCC usually called control that does abort if it's continuation isn't used and use that. I'm not a big fan of call/cc in general; I much prefer control. Control.Monad.Cont does export the Cont data constructor so you can easily add it yourself.

Hi, I finally was able to write a function which grabs the remainder of the computation in Cont monad and passes it to some function, in the same time forcing the whole computation to finish by returning a final value. I am not sure what kind of wheel I have reinvented, but here it is: ------------------------------------ -- Home-grown continuation delimiter function. Passes remainder of the -- whole computation to a given function and forces the whole computation -- to complete by returning a final value. Something similar to returning -- a final value in plain CPS instead of invoking the continuation. -- f: function which the remainder of the program will be passed to. -- Remainder will not be evaluated. -- r: final value of the whole computation that the latter will be -- terminated with. delimit f r = Cont $ \c -> runCont (return 0) $ \a -> f (runCont (return a) c) r ------------------------------------ I have created a simple (pseudo) concurrency demo that runs in a web browser, see the wiki page: http://haskell.org/haskellwiki/Concurrency_demos/Haskell-Javascript_concurre... Thanks. -- Dimitry Golubovsky Anywhere on the Web

On Thu, 2007-11-22 at 01:01 -0500, Dimitry Golubovsky wrote:
Hi,
I finally was able to write a function which grabs the remainder of the computation in Cont monad and passes it to some function, in the same time forcing the whole computation to finish by returning a final value.
I am not sure what kind of wheel I have reinvented, but here it is:
------------------------------------ -- Home-grown continuation delimiter function. Passes remainder of the -- whole computation to a given function and forces the whole computation -- to complete by returning a final value. Something similar to returning -- a final value in plain CPS instead of invoking the continuation. -- f: function which the remainder of the program will be passed to. -- Remainder will not be evaluated. -- r: final value of the whole computation that the latter will be -- terminated with.
delimit f r = Cont $ \c -> runCont (return 0) $ \a -> f (runCont (return a) c) r
This is more complicated than it needs to be. runCont (return 0) = \k -> k 0 so delimit f r = Cont $ \c -> f (c 0) r

Dimitry Golubovsky wrote:
If I have
callCC $ \exit -> do foo ...
I cannot jump to `exit' from within foo unless `exit' is given to foo as an argument.
As Derek Elkins has written, one of the options is to use delimited continuations, see http://research.microsoft.com/~simonpj/papers/control/ for Haskell implementation. But in this case Cont may be enough. If you don't like passing `exit' explicitly, you can put in into Reader monad. This is the idea: -------------------------------------------------------------------- import Control.Monad.Cont import Control.Monad.Reader type Abortable r a = ReaderT (r -> Cont r r) (Cont r) a runAbortable :: Abortable a a -> a runAbortable m = runCont (callCC $ \exit -> runReaderT m exit) id abort :: r -> Abortable r a abort x = do exit <- ask lift (exit x) undefined -- this hack is needed to make abort polymorphic test a b c = do x <- if a then abort "a" else return 1 y <- if b then abort "b" else return False z <- foo c -- calling foo without explicit abort continuation return $ show (x, y, z) where foo True = abort "c" foo False = return 5.39 run m = putStrLn (runAbortable m) main = do run (test False False False) run (test False False True) run (test False True False) run (test True False False) ------------------------------------------------------------------ This implementation is a bit hackish, since it uses undefined to make abort polymorphic in return type. You can use rank-2 types to avoid it, see http://www.vex.net/~trebla/tmp/ContMonad.lhs by Albert C. Lai.

On Tue, 2007-11-20 at 13:22 +0200, Gleb Alexeyev wrote:
Dimitry Golubovsky wrote:
If I have
callCC $ \exit -> do foo ...
I cannot jump to `exit' from within foo unless `exit' is given to foo as an argument.
As Derek Elkins has written, one of the options is to use delimited continuations, see http://research.microsoft.com/~simonpj/papers/control/ for Haskell implementation.
I made no such suggestion. I simply suggested using instead of callCC f = Cont (\k -> runCont (f (\a -> Cont $ \_ -> k a)) k) with control f = Cont (\k -> runCont (f (\a -> Cont $ \_ -> k a)) id) abort is then simply abort = control . const . return callCC is obviously just callCC f = control (\k -> f k >>= k) If you didn't want to "break abstraction" like this, you can implement this in terms of just callCC awkwardly. To do so requires having a top-level continuation and is exactly what is below. The above and below is (part of) why I prefer control.
But in this case Cont may be enough. If you don't like passing `exit' explicitly, you can put in into Reader monad. This is the idea:
-------------------------------------------------------------------- import Control.Monad.Cont import Control.Monad.Reader
type Abortable r a = ReaderT (r -> Cont r r) (Cont r) a
runAbortable :: Abortable a a -> a runAbortable m = runCont (callCC $ \exit -> runReaderT m exit) id
abort :: r -> Abortable r a abort x = do exit <- ask lift (exit x) undefined -- this hack is needed to make abort polymorphic
test a b c = do x <- if a then abort "a" else return 1 y <- if b then abort "b" else return False z <- foo c -- calling foo without explicit abort continuation return $ show (x, y, z) where foo True = abort "c" foo False = return 5.39
run m = putStrLn (runAbortable m)
main = do run (test False False False) run (test False False True) run (test False True False) run (test True False False)
------------------------------------------------------------------
This implementation is a bit hackish, since it uses undefined to make abort polymorphic in return type. You can use rank-2 types to avoid it, see http://www.vex.net/~trebla/tmp/ContMonad.lhs by Albert C. Lai.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Derek Elkins wrote:
As Derek Elkins has written, one of the options is to use delimited continuations, see http://research.microsoft.com/~simonpj/papers/control/ for Haskell implementation.
I made no such suggestion.
I didn't mean that you suggested using implementation referenced above. But you suggested using 'control' which is obviously a delimited control operator and that is what I was trying to say.

gleb.alexeev:
Derek Elkins wrote:
As Derek Elkins has written, one of the options is to use delimited continuations, see http://research.microsoft.com/~simonpj/papers/control/ for Haskell implementation.
I made no such suggestion.
I didn't mean that you suggested using implementation referenced above. But you suggested using 'control' which is obviously a delimited control operator and that is what I was trying to say.
While we're here, it might be a good time to remind people also that we've got: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CC-delcont-0.1 An implementation of multi-prompt delimited continuations based on the paper, A Monadic Framework for Delimited Continuations, by R. Kent Dybvig, Simon Peyton Jones and Amr Sabry It also includes a corresponding implementation of dynamically scoped variables, as implemented in the paper, Delimited Dynamic Binding, by Oleg Kiselyov, Chung-chieh Shan and Amr Sabry sitting on hackage, thanks to the work of Dan Doel, who jumped in to fill a gap in the libraries. -- Don
participants (4)
-
Derek Elkins
-
Dimitry Golubovsky
-
Don Stewart
-
Gleb Alexeyev