evaluate to lazy?

Duncan Coutts duncan.coutts at worc.ox.ac.uk
Tue Nov 21 07:34:33 EST 2006


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



More information about the Glasgow-haskell-users mailing list