
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? Thanks, Andreas PS: I circumvent this issue by using 'rnf' and 'using' from Control.Parallel.Strategies

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

On Tue, 2006-11-21 at 09:53 +0100, Andreas Marth wrote:
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?
(glossing over the issue of return in IO) a,b) "error#some error message" c) ' ' : error "error#some error message" note that c) is not _|_. What about this one: d) fmap head (guess [" "]) yep, it returns ' ', no error.
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?
The point is that: _|_ /= 1 : 2 : _|_ so doing evaluate (1 : error "argh") doesn't throw any error since (1 : error "argh") is not an error value (though it does contain one).
PS: I circumvent this issue by using 'rnf' and 'using' from Control.Parallel.Strategies
That's a sensible strategy since then you force the whole list and will uncover any _|_ values inside the data structure. Duncan

On Tue, 2006-11-21 at 09:53 +0100, Andreas Marth wrote:
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?
(glossing over the issue of return in IO)
a,b) "error#some error message" c) ' ' : error "error#some error message"
note that c) is not _|_.
What about this one:
d) fmap head (guess [" "])
yep, it returns ' ', no error.
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
I know that 1:error "emsg" is not _|_. What is surprising for me is that
evaluate ( 1:error "emsg") does not raise an exception.
Therefore I have 2 points:
1.) I think evaluate should have more explanation in the library
documentation. (I read Alastair Reid: "Handling Exceptions in Haskell" and
Simon PEYTON JONES: "Tackling the Awkward Squad" and still missed this
point.) I think the following from "Tackling the Awkward Squad" (p. 41) is a
good candidate:
"a1, a2, a3, a4 :: IO ()
a1 = do { x <- evaluate 4; print x }
a2 = do { evaluate (head []); print "no" }
a3 = do { return (head []); print "yes" }
a4 = do { xs <- evaluate [1 `div` 0]; print (length xs) }
The first simply evaluates 4, binds it to x, and prints it; we could equally
well have written (return 4) instead. The second evaluates (head []), finds
an exceptional value, and throws an exception in the IO monad; the following
print never executes. In contrast a3 instead returns the exceptional value,
ignores it, and prints yes. Lastly, a4 evaluates the list [1 'div' 0], binds
it to xs, takes its length, and prints the result. The list contains an
exceptional value, but evaluate only evalutes the top level of its argument,
and does not look inside its recursive tructure"
2.) Is it useful that evaluate is not 'really strict' (does not fully
evaluate its argument)?
If I use
a5 = do {xs <- return [1 `div` 0]; print (length xs)}
it is the same as a4. The exceptional value within the list is never
evaluated and so the print succeeds.
So why did I use evaluate [1 `div` 0] in the first place?
The same is true with my excample with a String:
a6 = do {xs <- evaluate ("text"++error "emsg"); print xs}
a7 = do {xs <- return ("text"++error "emsg"); print xs}
which both rise an exception. (In both cases the execution of print rises
it.) Which is different from
a8 = do {xs <- evaluate (error "emsg"); print xs}
where evaluate raises the exception.
a9 = do {xs <- return (error "emsg"); print xs}
has the same output as a8 (which is different than a6 and a7) but is raised
by print again.
This all is not of great interest if you do not try to catch the possible
exception. If you also want to get accurate strings it gets complicated.
If you just try to catch an exception while printing
a10 = do {xs <- return ("text"++error "emsg"); catch (print xs) (\e -> print
e)}
You get the string mixed with the error message.
The same goes when you use
a11 = do {xs <- evaluate ("text"++error "emsg"); catch (print xs) (\e ->
print e)}
If your string starts with the error then
a12 = do {xs <- evaluate ((error "emsg") ++ "123"); catch (print xs) (\e ->
print e)}
still raises an exception while
a13 = do {xs <- return ((error "emsg") ++ "123"); catch (print xs) (\e ->
print e)}
gives only the error message.
So I would say the return version is closer to what I want.
What I really want is that I force all the exceptions and catch them. In the
above excamples this would be something like
a14 = do {xs <- return ("Text" ++ error "emsg" ++ "123"); catch (print
(using xs rnf)) (\e -> print e)}
or
a15 = do {xs <- return (using ("Text" ++ error "emsg" ++ "123") rnf); catch
(print xs) (\e -> print e)}
And instead of "return (using a rnf)" I would like to write "evaluate a".
To sum it up:
- For my usage "evaluate a" is equal to "return a" (What are the cases where
"evaluate a" is different from "return $! a"? Stated in the library
documentation (Control.Exception).)
- I don't see where evaluate in its current form is better than "return a"
- I think "evaluate a" should mean "return (using a rnf)"
Do I miss something important here?
Does anybody use evaluate in a way that depends on it current definition?
Thanks for any comments,
Andreas
----- Original Message -----
From: "Duncan Coutts"
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?
The point is that:
_|_ /= 1 : 2 : _|_
so doing
evaluate (1 : error "argh")
doesn't throw any error since (1 : error "argh") is not an error value (though it does contain one).
PS: I circumvent this issue by using 'rnf' and 'using' from Control.Parallel.Strategies
That's a sensible strategy since then you force the whole list and will uncover any _|_ values inside the data structure.
Duncan

Though I'm not an expert, I'll give it a try. Am Mittwoch, 22. November 2006 14:23 schrieb Andreas Marth:
I know that 1:error "emsg" is not _|_. What is surprising for me is that evaluate ( 1:error "emsg") does not raise an exception.
evaluate is defined (in 6.4.2, didn't find the 6.6 sources so quickly) as evaluate :: a -> IO a evaluate a = IO $ \s -> case a `seq` () of () -> (# s, a #) so it evaluates its argument just like seq (I believe it reduces a to whnf) and since (1:error "emsg") is of the form (_:_), which is not _|_, no exception is raised. The difference to a `seq` return a is, as far as I can see, that (undefined `seq` return undefined) `seq` someAction === _|_, while evaluate undefined `seq` someAction === someAction, because evaluate undefined is of the form IO something, hence _not_ _|_. Says the doc: "It can be used to order evaluation with respect to other IO operations" and indeed it can, however, the doc also says that it forces its argument to be evaluated, which is probably a bit misleading (like the notion that seq forces its first argument to be evaluated - only so much that we know if it's _|_ or not).
Therefore I have 2 points:
1.) I think evaluate should have more explanation in the library documentation.
Yes, would be nice.
(I read Alastair Reid: "Handling Exceptions in Haskell" and Simon PEYTON JONES: "Tackling the Awkward Squad" and still missed this point.) I think the following from "Tackling the Awkward Squad" (p. 41) is a good candidate: "a1, a2, a3, a4 :: IO () a1 = do { x <- evaluate 4; print x } a2 = do { evaluate (head []); print "no" } a3 = do { return (head []); print "yes" } a4 = do { xs <- evaluate [1 `div` 0]; print (length xs) } The first simply evaluates 4, binds it to x, and prints it; we could equally well have written (return 4) instead. The second evaluates (head []), finds an exceptional value, and throws an exception in the IO monad; the following print never executes. In contrast a3 instead returns the exceptional value, ignores it, and prints yes. Lastly, a4 evaluates the list [1 'div' 0], binds it to xs, takes its length, and prints the result. The list contains an exceptional value, but evaluate only evalutes the top level of its argument, and does not look inside its recursive structure"
2.) Is it useful that evaluate is not 'really strict' (does not fully evaluate its argument)?
Same applies to seq, you want a deepEvaluate it seems. I don't know about the pros and cons of evaluating to rnf or whnf, so wait for the experts to answer that.
If I use a5 = do {xs <- return [1 `div` 0]; print (length xs)} it is the same as a4. The exceptional value within the list is never evaluated and so the print succeeds. So why did I use evaluate [1 `div` 0] in the first place?
To distinguish _|_ and [_|_]?
The same is true with my excample with a String: a6 = do {xs <- evaluate ("text"++error "emsg"); print xs} a7 = do {xs <- return ("text"++error "emsg"); print xs} which both rise an exception. (In both cases the execution of print rises it.) Which is different from a8 = do {xs <- evaluate (error "emsg"); print xs} where evaluate raises the exception. a9 = do {xs <- return (error "emsg"); print xs} has the same output as a8 (which is different than a6 and a7) but is raised by print again.
This all is not of great interest if you do not try to catch the possible exception. If you also want to get accurate strings it gets complicated. If you just try to catch an exception while printing a10 = do {xs <- return ("text"++error "emsg"); catch (print xs) (\e -> print e)} You get the string mixed with the error message. The same goes when you use a11 = do {xs <- evaluate ("text"++error "emsg"); catch (print xs) (\e -> print e)} If your string starts with the error then a12 = do {xs <- evaluate ((error "emsg") ++ "123"); catch (print xs) (\e -> print e)} still raises an exception while a13 = do {xs <- return ((error "emsg") ++ "123"); catch (print xs) (\e -> print e)} gives only the error message. So I would say the return version is closer to what I want. What I really want is that I force all the exceptions and catch them. In the above excamples this would be something like a14 = do {xs <- return ("Text" ++ error "emsg" ++ "123"); catch (print (using xs rnf)) (\e -> print e)} or a15 = do {xs <- return (using ("Text" ++ error "emsg" ++ "123") rnf); catch (print xs) (\e -> print e)}
I posted a suggestion yesterday, xs <- mapM (\x -> catch (evaluate x) errorHandler) ys might do what you want, in case of ys = ["good", error "bad", "goodAgain"], xs would contain three nice values (if the errorHandler is good), however for ys = ["goo" ++ error "nay", error "bad", "good"], the eroor "nay" would pass unhandled. Or you might define reduce a = return (using a rnf) and use reduce instead of evaluate.
And instead of "return (using a rnf)" I would like to write "evaluate a".
To sum it up: - For my usage "evaluate a" is equal to "return a" (What are the cases where "evaluate a" is different from "return $! a"? Stated in the library documentation (Control.Exception).) - I don't see where evaluate in its current form is better than "return a" - I think "evaluate a" should mean "return (using a rnf)"
Do I miss something important here? Does anybody use evaluate in a way that depends on it current definition?
Thanks for any comments, Andreas
Cheers, Daniel
----- Original Message ----- From: "Duncan Coutts"
To: "Andreas Marth" Cc: Sent: Tuesday, November 21, 2006 1:34 PM Subject: Re: evaluate to lazy? On Tue, 2006-11-21 at 09:53 +0100, Andreas Marth wrote:
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?
(glossing over the issue of return in IO)
a,b) "error#some error message" c) ' ' : error "error#some error message"
note that c) is not _|_.
What about this one:
d) fmap head (guess [" "])
yep, it returns ' ', no error.
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?
The point is that:
_|_ /= 1 : 2 : _|_
so doing
evaluate (1 : error "argh")
doesn't throw any error since (1 : error "argh") is not an error value (though it does contain one).
PS: I circumvent this issue by using 'rnf' and 'using' from Control.Parallel.Strategies
That's a sensible strategy since then you force the whole list and will uncover any _|_ values inside the data structure.
Duncan
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (3)
-
Andreas Marth
-
Daniel Fischer
-
Duncan Coutts