Delimited continuations: please comment

Hi, I'm experimenting with delimited continuations in the effort to understand how they work and when it's convenient to use them. Consider this piece of code (install the CC-delcont before running it): ---- {-# LANGUAGE NoMonomorphismRestriction #-} import Control.Monad.CC import Control.Monad.Trans -- why do I have to import this? data Monad m => Susp m a b = Stop | Susp (a -> m (Susp m a b)) job = reset $ \p -> let askMsg = shift p $ \k -> return $ Susp $ k . return in do x <- askMsg liftIO $ putStrLn $ "x was " ++ show x y <- askMsg liftIO $ putStrLn $ "y was " ++ show y return Stop scheduler j = do Susp nj <- j Susp nj <- nj "Hello!" nj "World!" return undefined main = runCCT $ scheduler job ---- which produces the output: ---- [paris@bagend haskell]$ runhaskell dc.hs x was "Hello!" y was "World!" [paris@bagend haskell]$ ---- The goal of this is to have a test-case implementation of the system call mechanism found in operating systems, like the one described by Oleg in (see page 3): http://okmij.org/ftp/papers/context-OS.pdf In effect, this is a bit different from the syscall service routine described by Oleg, as the scheduler function reacts in different ways for subsequent calls (the first time feeds "Hello!", the second one "World!", in a nice monad style). Yet, I liked the separation between the scheduler and the job, which are two completely different values and which I tried to keep. As this is (almost) my first time using delconts, could you provide feedback, comments, opinions about my piece of code and the topic in general (convenience, performances, alternatives and so on)? Thank you, Cristiano

Cristiano Paris
In effect, this is a bit different from the syscall service routine described by Oleg, as the scheduler function reacts in different ways for subsequent calls (the first time feeds "Hello!", the second one "World!", in a nice monad style). Yet, I liked the separation between the scheduler and the job, which are two completely different values and which I tried to keep.
It's not unheard of for the scheduler to react in different ways to the same system call -- I'm thinking of reading from a file, for example.
As this is (almost) my first time using delconts, could you provide feedback, comments, opinions about my piece of code and the topic in general (convenience, performances, alternatives and so on)?
You clearly understand the whole idea, and your code demonstrates it in a nice way. Oleg and I have found this programming style particularly convenient when we need to - fork processes (i.e., backtrack in the monad), - run the same processes under different schedulers (e.g., a debugger), - nest the applications of schedulers (i.e., provide virtualization). -- Edit this signature at http://www.digitas.harvard.edu/cgi-bin/ken/sig "Attending a mathematics lecture is like walking through a thunderstorm at night. Most of the time you are lost, wet and miserable but at rare intervals there is a flash of lightening and the whole countryside is lit up." - Tom Koerner

On Fri, Feb 13, 2009 at 2:05 AM, Chung-chieh Shan
... It's not unheard of for the scheduler to react in different ways to the same system call -- I'm thinking of reading from a file, for example.
Sure, I went implementing something slitghtly different to double check my understanding of delconts.
You clearly understand the whole idea, and your code demonstrates it in a nice way. Oleg and I have found this programming style particularly convenient when we need to - fork processes (i.e., backtrack in the monad), - run the same processes under different schedulers (e.g., a debugger), - nest the applications of schedulers (i.e., provide virtualization).
Thanks for your feedback. Cristiano

On 2009 Feb 12, at 11:55, Cristiano Paris wrote:
import Control.Monad.Trans -- why do I have to import this?
liftIO is defined there, I believe. Many of the monad modules re- export it with their MonadTrans definitions, but apparently Control.Monad.CC doesn't so you need to go to the source. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Sat, Feb 14, 2009 at 2:04 AM, Brandon S. Allbery KF8NH
liftIO is defined there, I believe. Many of the monad modules re-export it with their MonadTrans definitions, but apparently Control.Monad.CC doesn't so you need to go to the source.
Yeah, I knew the answer :D It was sort of a joke... Cristiano
participants (4)
-
Brandon S. Allbery KF8NH
-
Chung-chieh Shan
-
Cristiano Paris
-
Cristiano Paris