[Haskell-cafe] Delimited continuations: please comment
Cristiano Paris
cristiano.paris at gmail.com
Thu Feb 12 11:55:49 EST 2009
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 at bagend haskell]$ runhaskell dc.hs
x was "Hello!"
y was "World!"
[paris at 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
More information about the Haskell-Cafe
mailing list