
Am Dienstag, 21. November 2006 09:53 schrieb Andreas Marth:
Hi!
With the following code:
module Guess where
import Prelude hiding (catch) import Control.Exception (evaluate, catch)
guess :: [String] -> IO String guess sl = do res <- catch (evaluate (concat $ sl ++ [error "some error message", "blah blah blah"])) (\e -> return ("error#"++show e)) return res -- only for demonstration coded like this normally a call to sysalloc comes here
what will a) guess [] b) guess [""] c) guess [" "]
return?
The idea was to return the string, catch every error if any occour, convert it into a string and prefix it with "error#" and return this string then. The reason to do this is to create a stable DLL with the error handling in non haskell land. At the moment every exception raised crashes the whole system, which is unacceptable. Unfortunately the c) case still raises an exception. I think at least the library description needs a hint that 'evaluate (" "++error "some error message")' does not raise the error (which I find strange!) and hence catch won't catch it. Is this behaivior really desired or should we consider it a bug?
Well, evaluate doesn't _fully_ evaluate its argument and in case c) it sees that the argument of evaluate is of the form (_:_), so no cause to raise the exception, like *Guess> (" " ++ error "Hah!") `seq` "Huh!" "Huh!" *Guess> ("" ++ error "Hah!") `seq` "Huh!" "*** Exception: Hah! Maybe this is what you want? guess2 :: [String] -> IO String guess2 sl = do res <- mapM (\s -> (catch (evaluate s) (\e -> return ("error#" ++ show e)))) (sl ++ [error "MyMess", "Blah blub"]) return $ concat res *Guess> guess2 [" "] " error#MyMessBlah blub" Cheers, Daniel
Thanks, Andreas
PS: I circumvent this issue by using 'rnf' and 'using' from Control.Parallel.Strategies
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users