
Hi, I've got an IO action, some file system IO, traversing one level only and iterating over files found. I wish to build in an "early" exit, ie. if an IO action in the loop encounters a particular value I want it to abort the loop. Now so far, pls don't shoot, I have done this by throwing IO Exceptions and catching them. I'm trying to rewrite this using Continuatios / callCC but can't figure out where to place what. I certainly don't have the intuition yet and funny enough not even in RWH I could find some Cont/ContT examples. Would someone please draw me an example? Günther

Well, continuations come from Scheme, and by and large, they are usually
used in languages like Scheme (i.e. PLT web server), or Smalltalk (Seaside
web server), but they can be very useful in e.g. cases like yours for making
a convenient way to make a local exit. I did this in one toy game program
of mine. The code looks (somewhat) like this:
run :: GameState ()
run = (`runContT` id) $ do
throwaway <- callCC $ \exit -> forever $ do
-- retrieve the current state
-- get user input, etc...
case input of
...
"quit" -> exit $ return ()
in this case, when the user enters "quit" the captured continuation is
restored and the value '()' is returned from callCC and assigned to
'throwAway' in this case.
Of course, this is only one use case of continuations, a very powerful
abstraction mechanism :)
Cheers.
2009/7/3 Günther Schmidt
Hi,
I've got an IO action, some file system IO, traversing one level only and iterating over files found. I wish to build in an "early" exit, ie. if an IO action in the loop encounters a particular value I want it to abort the loop.
Now so far, pls don't shoot, I have done this by throwing IO Exceptions and catching them. I'm trying to rewrite this using Continuatios / callCC but can't figure out where to place what.
I certainly don't have the intuition yet and funny enough not even in RWH I could find some Cont/ContT examples.
Would someone please draw me an example?
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Couldn't resist taking the bait...
Well, continuations come from Scheme, and by and large, they are usually used in languages like Scheme (i.e. PLT web server), or Smalltalk (Seaside web server),
For a fuller history of continuatios, please see "The Discoveries of Continuations" by John Reynolds (http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.40.237) -Jeff

Here's some code I wrote the other day:
hasCycle :: (Applicative m, MonadIO m) => Node -> m Bool
hasCycle n0 = runContT (*callCC* go) return
where
go *abort* = do visit [] IM.empty n0
return False
where
visit preds h n = do
nid <- nodeId n
h' <- foldM (\h' n' -> do
n'id <- nodeId n'
case IM.lookup n'id h' of
Just True -> *abort* True
Just False -> return h'
Nothing -> visit (n:preds) h n')
(IM.insert nid True h) =<< nodeChildren n
return (IM.insert nid False h')
This function returns True if the graph starting at n0 has cycles. You can
ignore the details; take a look at the use of "abort". The type of "abort"
is Bool -> m (IM.IntMap Bool) but the result type is actually irrelevant
since this function will never return. The effect of calling "abort" is to:
jump back to the place where we called callCC and replace the call with the
value we passed to "abort".
You can think of callCC of creating a snapshot of the program's current
execution state. This snapshot (called the "current continuation") is
passed to the function that was the argument to "callCC" ("go" in the
above). This snapshot is represented as a function and you can call it.
If you call the continuation, two things happen:
1. The currently executed code is aborted.
2. The execution jumps back to the state in which callCC was called and the
call to callCC gets replaced by the value you passed to the continuation.
Naturally, we cannot undo IO effects, so not all of the state is reset.
Also, since callCC is only available in the monad, it only saves the
snapshot up to the closest "runContT".
Another, more mind-bending feature of continuations is that you can store
them and invoke them *multiple times*. But that is a story for another day.
HTH
2009/7/4 Günther Schmidt
Hi,
I've got an IO action, some file system IO, traversing one level only and iterating over files found. I wish to build in an "early" exit, ie. if an
IO
action in the loop encounters a particular value I want it to abort the loop.
Now so far, pls don't shoot, I have done this by throwing IO Exceptions and catching them. I'm trying to rewrite this using Continuatios / callCC but can't figure out where to place what.
I certainly don't have the intuition yet and funny enough not even in RWH I could find some Cont/ContT examples.
Would someone please draw me an example?
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Push the envelope. Watch it bend.

Günther Schmidt wrote:
Hi,
I've got an IO action, some file system IO, traversing one level only and iterating over files found. I wish to build in an "early" exit, ie. if an IO action in the loop encounters a particular value I want it to abort the loop.
Now so far, pls don't shoot, I have done this by throwing IO Exceptions and catching them. I'm trying to rewrite this using Continuatios / callCC but can't figure out where to place what.
I certainly don't have the intuition yet and funny enough not even in RWH I could find some Cont/ContT examples.
Would someone please draw me an example?
The quick and dirty explanation is, given an expression like: f . g . h $ callCC (\k -> body) we might wonder what the meaning of "callCC (\k -> body)" is. If k is unused in body, then it means the same thing as "body" which is to say that body returns with some value x::A. The alternative is that we use k in the body (e.g. by passing it some y::A), in which case the value of "callCC (\k -> body)" is whatever value is passed to k (namely y::A). Note that the input type of k and the output type of body must be the same, and the output type of k is irrelevant because it never returns. Once we get a value for "callCC (\k -> body)", whatever value that is gets passed on to h, then g, then f, in the usual manner. For imperative code, this is just like calling return before the end of the function, e.g: if_PA_then_return5_else_DoSomethingAndReturnB = \ p a b -> callCC $ \exit -> do isP <- if p a then exit (return 5) -- return 5 *immediately* to our caller else return True -- if we ever get here, isP must equal True because -- exit never returns. doSomething -- if we wanted doSomething to be able to override our -- "return b" result, we could pass it exit and then -- doSomething will either return control to us (and we -- return b) or it will return directly to our caller with -- some other answer. return b That isn't the whole story, but it's enough to figure out how to do early exits. In the more compleat explanation, the k which callCC causes to be passed to its functional argument is the "f . g . h" which will be invoked after callCC returns. That is, it's not the composition of functions, but rather it's that exact application of those functions. I.e. the fabricated k is a goto statement accepting a value and returning control to just outside of the invocation of callCC. Because of this behavior you can do interesting things like returning k from the body, or passing k to itself, which allows someone else to jump back into the expression and rerun it by passing a new value through the "f . g . h" Another paper to check out if you're a fan of theory is: Andrzej Filinski Declarative continuations: An investigation of duality in programming language semantics http://www.springerlink.com/content/m2105282ru426654/ which does quite a good job of investigating how to reason about continuations. (Though you need to be somewhat familiar with some Category Theory, and intimately familiar with lambda calculus, to enjoy it.) -- Live well, ~wren

Hello Günther, Saturday, July 4, 2009, 3:11:23 AM, you wrote:
I've got an IO action, some file system IO, traversing one level only and iterating over files found. I wish to build in an "early" exit, ie. if an IO action in the loop encounters a particular value I want it to abort the loop.
just make an explicit loop: process [] = return () process (file:files) = do x <- doit file if x>0 then process files else return () -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Matthias, Saturday, July 4, 2009, 6:39:30 PM, you wrote:
Or use a fold:
process' = foldl op True files op True file = doit file op False _ = False
foldM, probably, otherwise you will need to execute all actions before running fold -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

process' = foldl op True files op True file = doit file op False _ = False
Please pardon me. 'doit' should surely be able to do some IO:
import Data.Foldable import System.IO process' = foldlM op True files op True file = doit file op False _ = return False
were DoIt has the type FilePath -> IO Bool

Hi,
I've put the code that I wish to transform from using exceptions to using
continuations on hpaste:
?http://hpaste.org/fastcgi/hpaste.fcgi/view?id=6515#a6515
thanks
Günther
Am 04.07.2009, 01:11 Uhr, schrieb Günther Schmidt
Hi,
I've got an IO action, some file system IO, traversing one level only and iterating over files found. I wish to build in an "early" exit, ie. if an IO action in the loop encounters a particular value I want it to abort the loop.
Now so far, pls don't shoot, I have done this by throwing IO Exceptions and catching them. I'm trying to rewrite this using Continuatios / callCC but can't figure out where to place what.
I certainly don't have the intuition yet and funny enough not even in RWH I could find some Cont/ContT examples.
Would someone please draw me an example?
Günther
-- Erstellt mit Operas revolutionärem E-Mail-Modul: http://www.opera.com/mail/

Hi Günther, here is a solution with the Maybe Monad: http://hpaste.org/fastcgi/hpaste.fcgi/view?id=6515#a6515 Matthias.

P.S. See http://en.wikibooks.org/wiki/Haskell/Monad_transformers for some documentation.

P.P.S. Strange it does not seem to work with the paste. So here comes the solution by mail: module Consolidator.BusinessLogic.ConflictsResolved (consolidateDuplicates) where import System.FilePath import System.Directory import Control.Monad (filterM) import Control.Exception (throwIO) import System.Environment import Data.Maybe import Control.Monad import Control.Monad.Trans newtype MaybeT m a = MaybeT { runMaybeT :: m (Maybe a) } instance (Monad m) => Monad (MaybeT m) where (>>=) tmb_v f = MaybeT (runMaybeT tmb_v >>= \b_v -> case b_v of Nothing -> return Nothing Just v -> runMaybeT $ f v ) return = MaybeT . return . return instance MonadTrans MaybeT where lift mon = MaybeT (mon >>= return . Just) abort :: String -> MaybeT IO a abort reason = do lift . putStrLn $ reason MaybeT (return Nothing) {- The traversal is one directory deep only. I try to find out if every immediate subdirectory contains exactly one "*.gdr" file, and collect the path names in a list, sgls. Afterwards I append the contents of each such file to another file. I want to abort the whole process as soon as I encounter a directory that does not include exactly one *.gdr file. Currently I'm throwing exceptions but I'd prefer to rewrite this code to use continuations. -} consolidateDuplicates :: FilePath -> MaybeT IO () consolidateDuplicates fp = do dirs <- lift (getDirectoryContents fp) recs <- lift (filterM doesDirectoryExist $ map (fp >) $ filter (not . flip elem [".", ".."]) dirs) sgls <- mapM checkForSingle recs let cpy = fp > "Korrigiert.gdr" lift (copyFile (fp > "Konsolidiert.gdr") cpy) lift (mapM_ (\sgl -> do str <- readFile sgl appendFile cpy str) sgls) checkForSingle :: FilePath -> MaybeT IO FilePath checkForSingle fp = do cnt <- lift (getDirectoryContents fp) let fltr = filter ((== ".gdr") . takeExtension) case fltr cnt of [] -> abort ("The directory " ++ fp ++ " is empty") [f] -> return (fp > f) _ -> abort ("There is more than one file in the directory " ++ fp)
participants (7)
-
Bulat Ziganshin
-
Günther Schmidt
-
jeff p
-
Matthias Görgens
-
Thomas Schilling
-
Tim Wawrzynczak
-
wren ng thornton