Re: [Haskell] IO, exceptions and error handling

2004-06-15 Thread Ketil Malde
Tim Docker [EMAIL PROTECTED] writes:

 Of course... that was my second alternative error strategy. I'm
 interest in how/when people decide when to throw exceptions versus
 when to thread errors using monads, given that changing code from
 one to the other could be quite a big deal.

I generally use 'error' for any kind of situation that shouldn't
happen during normal execution.  For run-time situations that can be
dealt with gracefully, I use Maybe or Either, and try to deal with it
as low as possible.

I realize this is very simplistic, but IME, exception handling code
trying to deal with all kinds of possibilities for failure often
becomes very spaghettiized, just like excessive use of (the other kind
of) GOTO.  There are simply too many bad things that can happen, so I
prefer the (Erlang?) strategy of 'letting it crash'.

If I were building a large long-lived application, I would probably
build subsystems using the LIC philosophy, and catch errors and
restart subsystems from a monadic framework.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] IO, exceptions and error handling

2004-06-14 Thread Graham Klyne
I'm finding that a recurring theme in my work with Haskell libraries (and 
in particular the XML libraries) is the awkwardness of handling errors 
outside the IO monad.

While it's often very easy to write some code that performs some function, 
assuming that the inputs are valid, as soon as code is required to deal 
with incorrect input, life gets more complicated.  The choice seems to be 
that the functions have to be re-modelled to return a value that 
incorporates a possible error condition, or any such error condition 
results in a failure of the calling program, removing the the calling 
program's option to effect a recovery strategy.

The exception handling system made available in the IO monad is one way out 
of this awkwardness, but it's only available when the recovery code is 
coded to run in the I/O monad (or by using unsafePerformIO).  I find this 
is problematic when I'm trying to write a general purpose library that uses 
some other general-purpose library that can raise errors.

I can't see any fundamental reason why exception handling has to occur in 
the IO monad.

E.g. I'm not aware that something like this would break the Haskell type 
assurances:

class (Eq e, Show e, Show v) = Exception e v where
makeExcept  :: v - e
catchExcept :: a - (e-a) - a
throw  :: e - a
instance Exception IOError String where
makeExcept  = userError
catchExcept = catch
throw e = error (show e)
  -- for Haskell implementations that allow errors
  -- to be caught in the IO monad
I think a limited implementation may be possible using unsafePerformIO:
data MyException = MyException String
showEx (MyException s) = s
instance Exception MyException String where
makeExcept  = MyException
catchExcept a h = unsafePerformIO $ catch (return a)
throw e = fail (showEx e)
...
Another approach that occurs to me is to introduce an error Monad along the 
lines of that described by Philip Wadler as E in his Essence of 
functional programming paper [1].  (Or just use Either as an error monad?, 
which is part of what I've been doing with my XML work.)

The disadvantages I see here are:
(a) it requires existing code to be modified to return the error monad value.
(b) it imposes a strict sequencing on the order of computation, which as 
far as I can see is not necessary to achieve the required error 
handling.  For example, a computation that returns a result that is not 
actually used in a subsequent computation would still cause an exception;  e.g.
do { b - f1   -- False
   ; c - f2   -- raises exception
   ; d - f3   -- value required
   ; return (if b then c else d)
   }
(I know this could be coded differently to avoid the claimed problem, but 
to my mind it still illustrates unnecessary complexity compared with:
if f1 then f2 else f3
In effect, it requires the programmer to figure out the lazy evaluation 
sequences instead of letting the Haskell system do it.)

...
I'll note that I have reservations about using exception handling in 
imperative languages (because it disrupts the normal guarantees of 
execution flow), but I can't see any corresponding disadvatages to using 
exceptions in a purely functional language environment.

Are there any plans or thoughts for introducing more widely usable 
exception handling in Haskell 2?

#g
--
[1] http://homepages.inf.ed.ac.uk/wadler/papers/essence/essence.ps
and others, linked from: 
http://homepages.inf.ed.ac.uk/wadler/topics/monads.html
(cf. section 2.3)


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Keith Wansbrough
 I can't see any fundamental reason why exception handling has to occur in 
 the IO monad.

Read the paper _A Semantics for Imprecise Exceptions_.  The problem is that the 
evaluation order of Haskell would have to be fixed for this not to lose referential 
transparency.  What is the value of

catchExcept (show (makeExcept E1 + makeExcept E2)) (\x - x)

?  Haskell wouldn't be purely functional any more.

http://research.microsoft.com/~simonpj/Papers/imprecise-exn.htm

--KW 8-)
-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Duncan Coutts
On Mon, 2004-06-14 at 14:34, Graham Klyne wrote:
 I'm finding that a recurring theme in my work with Haskell libraries (and 
 in particular the XML libraries) is the awkwardness of handling errors 
 outside the IO monad.

With GHC You can throw exceptions in pure code but may only catch them
in the IO monad. As Keith pointed out this is because the language would
not be referentially transparent if you could catch exception in 'pure'
code.

This is often enough in most situations. If you need to catch the
exceptions too then you'll want an error monad of some sort.

Duncan

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Tim Docker
Keith Wansbrough wrote:

 Read the paper _A Semantics for Imprecise Exceptions_.  The 
 problem is that the evaluation order of Haskell would have to 
 be fixed for this not to lose referential transparency.  What 
 is the value of
 
 catchExcept (show (makeExcept E1 + makeExcept E2))
(\x - x)
 
 ?  Haskell wouldn't be purely functional any more.

As Graham Klyne indicated in a previous mail, in practice there
are two ways of dealing with errors in purely functional code:

  - capture possible errors in the result type. This will
probably force the use of a monad, with the subsequent
sequencing of operation and coding style.

  - throw an exception, and hence be unable to recover from
errors outside the IO monad.

Both of these approaches seem fairly invasive in their
effect on the code. Are people using haskell for real world
tasks happy with having to choose from these? The former is
more general, but any function that needs to be able to
fail or propagate failure will end up being a do {} block.

Tim

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Mark Carroll
On Mon, 14 Jun 2004, Keith Wansbrough wrote:
(snip)
 to lose referential transparency.  What is the value of

 catchExcept (show (makeExcept E1 + makeExcept E2)) (\x - x)

 ?  Haskell wouldn't be purely functional any more.
(snip)

We've already had these issues raised on haskell-cafe when I've been
wanting non-monadic synchronous exceptions. (-: The answer is that you
evaluate all branches sufficiently to discover all the exceptions raised,
and maybe have an ordering on exceptions such that you can return
answers deterministically (as a list of ones that occurred or
something). I'll be happy to follow discussion of this on haskell-cafe but
will be reluctant to say much that I've already said (e.g. in December
2002's Error Handling) for fear of boring everyone silly.

-- Mark
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Philippa Cowderoy
On Mon, 14 Jun 2004, Tim Docker wrote:

 Both of these approaches seem fairly invasive in their
 effect on the code. Are people using haskell for real world
 tasks happy with having to choose from these? The former is
 more general, but any function that needs to be able to
 fail or propagate failure will end up being a do {} block.


The ability to fail doesn't need the do notation, just use of return for
success - similar for propagating failure.

-- 
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Graham Klyne
Now I see it.  Thanks.
Thanks also for the reference.  Nice paper!
So now where do I stand?
I still think that being forced to handle exceptions in the IO monad is 
(sometimes) inconvenient, but I can now see why it is required for a 
rigorous language semantics.  My problem relates to wanting to be able to 
effect some level of recovery in one library component for errors that 
arise in another.  I thought about returning the entire set of exceptions, 
but I see that the implementation penalty is probably too high.

I assume the suggested mapException function [sect 5.4] remains 
unproblematic ... is it (or some equivalent) actually implemented?  I could 
imagine it being useful for mapping errors into a common framework;  e.g. 
to catch exceptions from an XML parser and return a common XML error 
exception, incorporating information from the original as additional 
diagnostic.

I think that the suggested unsafeIsException is appealing, since it allows 
some level of recovery action without (I think) opening up the insecurities 
of unsafePerformIO.  The idea that the semantics of programs that do no 
raise exceptions is not affected is particularly appealing.

#g
--
At 14:46 14/06/04 +0100, Keith Wansbrough wrote:
 I can't see any fundamental reason why exception handling has to occur in
 the IO monad.
Read the paper _A Semantics for Imprecise Exceptions_.  The problem is 
that the evaluation order of Haskell would have to be fixed for this not 
to lose referential transparency.  What is the value of

catchExcept (show (makeExcept E1 + makeExcept E2)) (\x - x)
?  Haskell wouldn't be purely functional any more.
http://research.microsoft.com/~simonpj/Papers/imprecise-exn.htm
--KW 8-)
--
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Tim Docker
Philippa Cowderoy wrote:

 The ability to fail doesn't need the do notation, just use of 
 return for success - similar for propagating failure.

I'm not sure I understand. Do you mean writing functions
like:

sqr x | x  0 = fail less than zero
  | otherwise = return (sqrt x)

If so, I don't see how I can use this without either do
or =:

test x = do
   v1 - sqr x
   v2 - sqr (x+1)
   return (v1+v2)

I can't (easily) write

text c = sqr x + sqr (x+1)

which was what I was getting at.

Tim
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Keith Wansbrough
 Philippa Cowderoy wrote:
 
  The ability to fail doesn't need the do notation, just use of 
  return for success - similar for propagating failure.
 
 I'm not sure I understand. Do you mean writing functions
 like:
 
 sqr x | x  0 = fail less than zero
   | otherwise = return (sqrt x)

s/fail/error/
s/return//

Then you can easily write

 I can't (easily) write
 
 text c = sqr x + sqr (x+1)

You just can't *catch* this outside the IO monad.

--KW 8-)
-- 
Keith Wansbrough [EMAIL PROTECTED]
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Tim Docker
Keith Wansbrough wrote:

 s/fail/error/
 s/return//
 
 Then you can easily write
 
  I can't (easily) write
  
  text c = sqr x + sqr (x+1)
 
 You just can't *catch* this outside the IO monad.

Of course... that was my second alternative error
strategy. I'm interest in how/when people decide
when to throw exceptions versus when to thread
errors using monads, given that changing code
from one to the other could be quite a big deal.

Tim
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread Alastair Reid

 I assume the suggested mapException function [sect 5.4] remains
 unproblematic ... is it (or some equivalent) actually implemented? 

http://etudiants.insia.org/~jbobbio/pafp/docs/base/Control.Exception.html#v%
3AmapException

The same page has a host of other useful operations.

Two useful capabilities that are missing in the actual implementation are:

1) Provision for routinely adding filename and line number.
   (Of course, we'd need some kind of compiler support for filling
   that info in.)

  data Exception = ... | Location SrcLoc Exception | ...

2) The ability to build up lists of exceptions perhaps by adding something 
like:

  data Exception = ... | Nested Exception Exception | ...

This would allow handlers to build 'stacks' of exceptions rather like the 
stackdumps Java exceptions produce.  For example:

  foo x = mapException (Nested (ErrorCall while in foo)) $ bar x
  bar x = mapException (Nested (ErrorCall while in bar)) $ baz x
  baz x = 1/x

  foo 0
  ==
  Nested (ErrorCall while in foo)
 (Nested (ErrorCall while in bar)
 (ArithException DivideByZero))

[Alternate names for 'Nested' welcome.  `WhileDoing` is my next best 
attempt :-)]

--
Alastair Reid
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread John Meacham
On Mon, Jun 14, 2004 at 05:41:03PM +0100, Keith Wansbrough wrote:
  Philippa Cowderoy wrote:
  
   The ability to fail doesn't need the do notation, just use of 
   return for success - similar for propagating failure.
  
  I'm not sure I understand. Do you mean writing functions
  like:
  
  sqr x | x  0 = fail less than zero
| otherwise = return (sqrt x)
 
 s/fail/error/
 s/return//

better yet, 
import Control.Monad.Identity

sqr' x = runIdentity (sqr x)

now sqr' behaves exactly as if you used 'error' and direct code, but the
monadic version is still available for those that care about it.
John


-- 
John Meacham - repetae.netjohn 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] IO, exceptions and error handling

2004-06-14 Thread David Menendez
Graham Klyne writes:

 Another approach that occurs to me is to introduce an error Monad
 along the lines of that described by Philip Wadler as E in his
 Essence of functional programming paper [1].  (Or just use Either
 as an error monad?, which is part of what I've been doing with my XML
 work.)

Control.Monad.Error defines a class MonadError and some instances that
provide the functionality of Wadler's E monad.

 The disadvantages I see here are: (a) it requires existing code to be
 modified to return the error monad value. (b) it imposes a strict
 sequencing on the order of computation, which as far as I can see is
 not necessary to achieve the required error handling.  For example, a
 computation that returns a result that is not actually used in a
 subsequent computation would still cause an exception;  e.g.
  do { b - f1   -- False
 ; c - f2   -- raises exception
 ; d - f3   -- value required
 ; return (if b then c else d)
 }
 (I know this could be coded differently to avoid the claimed problem,
 but to my mind it still illustrates unnecessary complexity compared
 with:
  if f1 then f2 else f3
 In effect, it requires the programmer to figure out the lazy
 evaluation sequences instead of letting the Haskell system do it.)

I usually do that as:

 do b - f1
if b then f2 else f3

It's only slightly more complex, it's lazy, and it works with any monad.

But your general point is still valid.

--

As for bridging errors from one library to another, if you use
MonadError e m rather than a specific error monad, you can do something
along these lines:

 import Control.Monad.Error
 
 data XmlError = X1 | X2 | X3 | XOther String
 deriving (Eq, Show)
 
 instance Error XmlError where
   strMsg = XOther
 
 
 data AppError = AppXmlError XmlError | AppOther String
 deriving (Eq, Show)
 
 instance Error AppError where
   strMsg = AppOther
 
 --
 
 xmlFunc :: (MonadError XmlError m)
 = String - m String
 xmlFunc str = throwError X1
 
 
 appFunc :: (MonadError AppError m)
 = String - m String
 appFunc s
   = do s' - mapError AppXmlError (xmlFunc s)
return (result:  ++ s')
 
 
 mapError :: (MonadError e m)
  = (e' - e) - ErrorT e' m a - m a
 mapError f m = runErrorT m = either (throwError . f) return

   -- n.b. runErrorT :: ErrorT e m a - m (Either e a)

 test :: String - Either AppError String
 test = appFunc
-- 
David Menendez [EMAIL PROTECTED] http://www.eyrie.org/~zednenem/
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell