Re: FW: Exceptions are too return values!

1998-06-16 Thread Fergus Henderson

On 16-Jun-1998, Simon L Peyton Jones <[EMAIL PROTECTED]> wrote:
> 
> [Fergus wrote:]
> > I thought about this problem some more, and I have realized that the
> > problem of nondeterminacy for Haskell exceptions would in fact be
> > considerably worse that I had previously considered.  The trouble is
> > that in the general case the problem is not just that the choice of
> > which exception is raised is nondeterministic -- instead, it would be
> > much worse: the choice of whether you raise an exception or loop
> > forever can be also be nondeterministic.  This occurs because of
> > expressions such as `0/0 + loop'.  Or, to take a more realistic (and
> > nasty) example, `f 0' where `f x = 1/x + g x' where `g x' happens to
> > loop if `x' is zero.
> 
> I don't agree that this is a problem.  If (g x) loops when x is zero
> then you should jolly well test for that:
> 
>   f x | x == 0= raise "x is zero"
>   | otherwise = 1/x + g x

Simon, I'm sure that a really thorough programmer such as yourself
would never forget to insert such a test.  But, as was recently
demonstrated on this mailing list ;-), I'm quite fallible.
I'm sure there are many other fallible Haskell programmers around.

To minimize the bugs in my programs, I use a lot of different tools
and techniques.  I write in languages that have a lot of static checking,
so that the compiler will catch a lot of my mistakes.  I get my colleagues
to review my code.  And last but not least, I test my code.

For the kind of bug referred to above, static checking isn't going to
help (at least not given the current state of the art -- no doubt
improvements are possible).  Code reviews would help, but my colleagues
are fallible too.  And this kind of bug is very difficult to test for. 
Not only is it difficult to construct test cases that exercise all the
exceptional cases, even that is not sufficient, since it might work
fine with one implementation and then fail with another.

So, I don't think it is reasonable to say that this is not a problem.
It may not be a big problem, but I do consider it a problem.

Now, we can certainly debate the likely frequency of such bugs, and
their cost, and compare this with the advantages and disadvantages
of exception handling.  In fact, it does seem likely that such
bugs would be very rare.  The cost of each such bug may be high,
but if they occur infrequently enough, then the overall cost will be small.
So maybe you just meant that it wasn't likely to be a significant problem
in practice.  If that was what you meant, then I'm inclined to agree
with you.

> I simply don't think it's reasonable to comletely prescribe
> the evaluation order of a lazy functional program.

Why not?  Because it would inhibit optimization?
This is true, but for some applications reliability (and hence
determinism) is much more important than efficiency.
For these applications, I think it would be reasonable
to specify the behaviour exactly, even if it means giving
up some optimization opportunities.  Do you agree?

Conversely, there are many applications for which efficiency
is more important than determinacy, so for those applications
I agree the behaviour should not be specified exactly.

Fortunately a single language can support both kinds of applications,
as I outlined in previous mail.

> At the moment, Haskell has the fiction that a divide-by-zero
> exception and non-termination are the same value, i.e. bottom.
> That allows us to say that the behaviour of
> 
>   f x = 1/x + g x
> 
> is identical regardless of whether "+" evaluates its first
> argument first or second.  But we all know that the behaviour
> in these two cases is quite different: one prints a message and
> halts, and the other fails to terminate.  So in this sense
> the behaviour of Haskell programs is already non-deterministic.

That's true, but since both the fatal error message and non-termination
constitute program bugs, this is not so much of a worry.
The nondeterminism doesn't make testing any more difficult, for example.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: FW: Exceptions are too return values!

1998-06-16 Thread Simon L Peyton Jones


> Simon, I'm sure that a really thorough programmer such as yourself
> would never forget to insert such a test.  But, as was recently
> demonstrated on this mailing list ;-), I'm quite fallible.
> I'm sure there are many other fallible Haskell programmers around.

Don't worry, I'm fallible all right, as much GHC bug mail demonstrates!

> Now, we can certainly debate the likely frequency of such bugs, and
> their cost, and compare this with the advantages and disadvantages
> of exception handling.  In fact, it does seem likely that such
> bugs would be very rare.  The cost of each such bug may be high,
> but if they occur infrequently enough, then the overall cost will be small.
> So maybe you just meant that it wasn't likely to be a significant problem
> in practice.  If that was what you meant, then I'm inclined to agree
> with you.

Yes, that's what I meant.  I'm probably guilty of overstatement.
I do strongly feel that the cost/benefit equation comes down strongly
on the side of the NDSet story.

> > I simply don't think it's reasonable to comletely prescribe
> > the evaluation order of a lazy functional program.
> 
> Why not?  Because it would inhibit optimization?

Not just that; it also places extra side conditions
on reasoning about programs: now any reasoning steps
have to preserve evaluation order.  

Incidentally, if you *do* want to preserve evaluation order
then you can always use "seq".  GHC guarantees not to move
evaluations past "seq".

Simon





Re: FW: Exceptions are too return values!

1998-06-16 Thread Hans Aberg

At 14:40 +0100 98/06/10, Simon L Peyton Jones wrote:
>Here's a reasonable design for exceptions in Haskell:

  A think one can use a monadic approach, as a monad
(X, unit_X, bind_X): HaskellX -> HaskellX
where HaskellX is and extension of Haskell with exceptions.

>* A value of Haskell type T can be
>   EITHER one of the values we know and love
>  (bottom, or constructor, or function,
>   depending on T),
>
>   OR it can be a set of exceptional values.

  So this says that X(T) = T | Exception, where Exception is a type in
HaskellX which labels objects in Haskell as exceptions. This monad is such
as old Haskell code can always be run in the new HaskellX.

>* raise :: String -> a
>  (raise s) returns a single exceptional value, named by string s

  I would suggest that an exception could not just be a string, but any
value in HaskellX.

>* All strict operations (case, +, etc) return the union of
>  the exceptional values returned by their strict arguments
>  For example, if both arguments to "+" return an exceptional value
>  then "+" returns both. Similarly, any strict context.

  Actually, if a function f in Haskell has type T, and is altered so that
it raises an exception, then its type becomes T | Exception. If a function
g: A -> B is altered to raise an exception, there is a difference between
the types
A -> (B | Exception)  and  (A | Exception -> B | Exception), but the monad
is such that one can always simplify to the latter, and one can use the
abbreviation
  (A -> B) | Exception
for the latter.

  So the type handling mechanism should not need to be that much more
complicated: Just replace T with T | Exception if the function raises an
exception. Functions that do not raise an exception can always be extended
to this, T | Exception, on the fly when encountering an exception via the
monad proeprties, so these functions need not get an altered type.

>* handle :: (String -> IO a) -> IO a -> IO a
>  (handle h a) tries to perform the action a.
>  If doing so delivers a set of exceptional values then
>  apply the exception handler h to the string that names
>  one of them.  It is not defined which of the exceptional
>  values is picked.

  Then handle() should not only handle strings and IO, but any Exception
(of course), and any action a.

  The handle function must be able to determine if it can handle the
exception, so it should have a function f: Exception -> Boolean as an extra
argument; the exception is handled only if this evaluates to "true" for the
exception it handles.

  Hans Aberg
  * Email: Hans Aberg 
  * Home Page: 
  * AMS member listing: 






RE: FW: Exceptions are too return values!

1998-06-16 Thread Hans Aberg

At 11:06 +0200 98/06/16, Erik Zuurbier wrote:
>... Exceptions are merely a way to structure
>the code, so that the main line and error handling can be neatly separated.

  This is the original idea, but I pointed out that exceptions are in fact
much deeper: They can be used as a programming technique too, and further,
many common language constructs (such as "return", "break", etc in C++) can
be viewed  as special cases of exception handling.

  Hans Aberg
  * Email: Hans Aberg 
  * Home Page: 
  * AMS member listing: 






RE: FW: Exceptions are too return values!

1998-06-16 Thread Erik Zuurbier


SLPJ writes:

>So I appear to be in disagreement here with Alex, Amr, and Fergus about
>the importance of being able to say precisely which exception is raised.
>I'm quite content with knowing which *set* of exceptions can be raised.

I have read many, but not all of the messages on this subject. Did any of those
shed any light on the intended use of exceptions? Maybe that could explain
the disagreement. I can imagine:
1) You use exceptions for debugging your program, with the goal (naive maybe)
that none will ever be raised in the final program.
2) You learn to rely on the defined behaviour, deterministic or not, and the final
program can be perfectly acceptable if it raises any number of exceptions as long
as they are caught and handled in time. Exceptions are merely a way to structure
the code, so that the main line and error handling can be neatly separated.

Erik Zuurbier






RE: FW: Exceptions are too return values!

1998-06-16 Thread Dave Tweed

On Tue, 16 Jun 1998, Erik Zuurbier wrote:

> I have read many, but not all of the messages on this subject. Did any of those
> shed any light on the intended use of exceptions? Maybe that could explain
> the disagreement. I can imagine:
> 1) You use exceptions for debugging your program, with the goal (naive maybe)
> that none will ever be raised in the final program.
> 2) You learn to rely on the defined behaviour, deterministic or not, and the final
> program can be perfectly acceptable if it raises any number of exceptions as long
> as they are caught and handled in time. Exceptions are merely a way to structure
> the code, so that the main line and error handling can be neatly separated.

There's a third case, I think:

3) You are writing code which may be reused (either by design or
fortuitous circumstance); consequently if any of your `externally usable'
functions can throw an exception, you can't rely upon the user reading and
understanding you code to the degree that they appreciate all the nuances
of exactly which exception was thrown in some intricate circumstance. (I
think haskell is still a way from the C++ situation where there are
distributed _binary libraries_ which can throw exceptions, so you can't
assume you can even read the source.) Thus you have to deliberately make
circumstances where knowing _exactly_ what the primary error is (rather
than just that `an error occurred whilst doing this overall thing')
exactly predictable yourself, strictifying code if necessary.


cheers, dave

email: [EMAIL PROTECTED]   "Taught the wife some html. __Bad
www.cs.bris.ac.uk/~tweed/pi.htm   move__." -- Alan Cox
work tel: (0117) 954-5253  





Re: FW: Exceptions are too return values!

1998-06-16 Thread Simon L Peyton Jones


> I thought about this problem some more, and I have realized that the
> problem of nondeterminacy for Haskell exceptions would in fact be
> considerably worse that I had previously considered.  The trouble is
> that in the general case the problem is not just that the choice of
> which exception is raised is nondeterministic -- instead, it would be
> much worse: the choice of whether you raise an exception or loop
> forever can be also be nondeterministic.  This occurs because of
> expressions such as `0/0 + loop'.  Or, to take a more realistic (and
> nasty) example, `f 0' where `f x = 1/x + g x' where `g x' happens to
> loop if `x' is zero.

I don't agree that this is a problem.  If (g x) loops when x is zero
then you should jolly well test for that:

f x | x == 0= raise "x is zero"
| otherwise = 1/x + g x


I simply don't think it's reasonable to comletely prescribe
the evaluation order of a lazy functional program.

At the moment, Haskell has the fiction that a divide-by-zero
exception and non-termination are the same value, i.e. bottom.
That allows us to say that the behaviour of

f x = 1/x + g x

is identical regardless of whether "+" evaluates its first
argument first or second.  But we all know that the behaviour
in these two cases is quite different: one prints a message and
halts, and the other fails to terminate.  So in this sense
the behaviour of Haskell programs is already non-deterministic.

The nice thing about the NDSet story is that it makes clear
precisely where the non-determinism occurs.  Equational reasoning
is not impaired, nor is the implementation penalised.  I think
it's a great idea.

So I appear to be in disagreement here with Alex, Amr, and Fergus about
the importance of being able to say precisely which exception is raised.
I'm quite content with knowing which *set* of exceptions can be raised.
Ha!

Simon






Re: FW: Exceptions are too return values!

1998-06-15 Thread Fergus Henderson

On 12-Jun-1998, Alastair Reid <[EMAIL PROTECTED]> wrote:
> 
> Fergus Henderson <[EMAIL PROTECTED]> points out that our exception handling
> scheme hits problems if you hit an infinite loop instead of an exception.
> 
> Yes, this is a problem - and not a pretty one.
> 
> Fixes:
...
> 3) Add timeouts (and ctrl-C handling) into the mix - practical
>approximations to solving the halting problem.
>
> Fergus then lists a bunch of options and says:
> 
> > Of these options, I'm afraid that (a), the status quo, is looking to me
> > like the best of a bad lot, albeit with (c) (i) a close second.
> 
> ... some of us have to write programs that keep working.  For example, 
> I'm busy hacking on our Robo-Haskell code at the moment - it just isn't
> acceptable for that kind of code to print an error message and halt.

For programs like that, where reliability is very important, wouldn't
it be better to use deterministic exceptions [i.e. (c)(i)], even if
it means giving up some optimization?

> As far as I can see, that means we either have to eliminate pattern
>  match failure, the error function, heap overflow, stack overflow
>  and infinite loops or we have to add exception handling in some form.

Well, eliminating pattern match failure would not be a bad idea.
I think it's better to require programmers to put explicit calls to `error'
if that's what they want.

Regarding infinite loops, and the use of the `error' function, in the
long term future I hope we see systems that have much better support
for the use of formal methods, so that system and the program could
between them provide proofs of termination and proofs that `error' is
never called.  Much work has already been done in this general area,
including some by some of my colleagues [1], but there is still much to
be done -- making this practical is still very much a research issue.

Regarding resource exhaustion such as heap overflow, stack overflow,
and (for hard real-time programs) timeouts, yes, you do need to provide
a way of handling these, and these are going be have to be nondeterministic,
at least from the program's point of view (that is, at the level of the
denotational semantics rather than the operational semantics).
But that doesn't necessarily mean that you should use the same
approach for other kinds of exceptions -- as noted in other messages
in this thread, resource failures are different to other kinds of exceptions.

I suppose that overall, the disadvantages of nondeterminstic exceptions
(compared to the status quo) for program portability and reliability 
is likely to be significantly outweighed by the advantage in expressiveness,
and the consequently increased robustness that they provide.
I was a bit shocked when first I realized that the nondeterminism could affect
termination so easily, but on reflection I guess that in the big picture
this is likely to be a rare event and so even nondeterministic exceptions
are likely to be a significant win overall.

However, for reliability and portability, if Haskell does end up
adopting nondeterministic exceptions, I'd like to see a requirement
that implementations offer an option which would inhibit any
optimizations that might affect which exceptions were thrown. 
The interface would remain the same (using NDSet and/or the IO monad),
so the effect of this option would just that the operational semantics
would be more tightly specificied.

[1]Termination analysis for Mercury. 
   Chris Speirs, Zoltan Somogyi and Harald Sondergaard.
   Technical Report 97/9, Department of Computer Science, University
   of Melbourne, Melbourne, Australia, July 1997, 25 pages.
   Available via .
   This paper presents the algorithms of the Mercury termination
   analyser, discusses how real-world aspects of the language such as
   modules, higher-order features, foreign language code, and
   declarative input/output can be handled, and evaluates the
   performance of the analyser both on a set of standard test
   programs and on the Mercury compiler itself.
   A shorter version of this paper was published in the
   Proceedings of the Fourth International Static Analysis Symposium,
   Paris, France, September 1997.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: FW: Exceptions are too return values!

1998-06-13 Thread Hans Aberg

At 15:02 -0700 98/06/12, Carl R. Witty wrote:
>And I agree with this list, except for infinite loops.  How will
>exceptions help make a program robust that otherwise might loop?

  There is no general method of finding the non-terminations (the problem
is proved unsolvable, I think), so from that generalistic point of view,
nothing will help, not exceptions, nor anything else.

  But one can think of scanning the code, and try to catch the most obvious
programming errors.

  When I tried to unify the different loop constructs of C++ semantically,
I found this version:
loop { ... break; ... }
It has two components, "loop" which loops forever until it hits the "break".

  Now this construction can be implemented using exceptions: "loop" is
equivalent to
try { ... throw Break; ...}
catch (Break&) { ... }

  So there appears to be some relation between (imperative) loops and
exceptions.

  Hans Aberg
  * Email: Hans Aberg 
  * Home Page: 
  * AMS member listing: 






Re: FW: Exceptions are too return values!

1998-06-13 Thread Fergus Henderson

On 11-Jun-1998, Amr A Sabry <[EMAIL PROTECTED]> wrote:
> A Java implementation is free to load and link classes in any order,
> strictly or lazily, but it MUST report exceptions as if it had loaded
> and resolved the classes lazily.
> 
> I think Haskell should have the same restriction: it would bad to
> receive different exceptions because a Haskell implementation decided
> to evaluate an argument strictly before it is needed. 

I thought about this problem some more, and I have realized that the
problem of nondeterminacy for Haskell exceptions would in fact be
considerably worse that I had previously considered.  The trouble is
that in the general case the problem is not just that the choice of
which exception is raised is nondeterministic -- instead, it would be
much worse: the choice of whether you raise an exception or loop
forever can be also be nondeterministic.  This occurs because of
expressions such as `0/0 + loop'.  Or, to take a more realistic (and
nasty) example, `f 0' where `f x = 1/x + g x' where `g x' happens to
loop if `x' is zero.

So, although I do think that for most applications it would be quite
acceptable for the choice of exception to potentially vary from
implementation to implementation or from run to run, since generally
this would not significantly affect the behaviour, this is not
sufficient.  And it is probably unacceptable for the termination or
nontermination to vary from implementation to implementation (or from
run to run, or according to optimization level), especially if the
differences show up only in exceptional cases which are difficult to
test for.

Thus, I think the whole idea of using nondeterminism to allow the
implementation the freedom to reorder code and yet still implement
exceptions in a simple and efficient manner has a significant flaw.

The wish to avoid this flaw leads us to reconsider using a deterministic
rule for which exception (or set of exceptions) is thrown.  One advantage
is that this would allow a deterministic interface -- no need to involve
NDSet or the IO Monad.
You could still preserve commutativity of operations such as `+',
if you choose the exception based on some canonical ordering,
or (better) if you return a set of exceptions, rather than a single exception
(this time it is a deterministic set, not a nondeterministic set).
However, this comes at the cost of having to establish an
exception handler for each call such operations.
But whether or not you decide to preserve commutative of such operations,
in the general case the implementation would *not* be free to reorder code,
at least not without doing a lot of fancy footwork to ensure that the set of
exceptions thrown remained the same.  And unless you have a C++-style
"zero overhead" exception mechanism, the overheads of that fancy footwork
would most likely outweigh the benefits.  Even then, the so-called
"zero overhead" mechanisms do have significant space overheads, and
due to locality issues these space overheads also result in time overheads.
So it's not at all clear that you could get a net win.

Thus to summarize the implications of deterministic exceptions, using a
deterministic rule would mean that in order to effectively implement
reordering optimizations for expressions that might throw exceptions,
an implementation would need to have an "zero-overhead" exception
mechanism (itself a *very* large cost in implementation complexity),
and they would need to do a lot of fancy footwork to establish the
right exception handlers whenever they reorder code (more
implementation complexity), and even then it is not clear that the
resulting optimizations would be a net win.  So, I'd say an implementor
need to be foolhardy to attempt such optimizations.  More likely, they
would apply reordering optimizations only where they can prove that the
code in question will not throw any exceptions.

The same criticism applies to using exceptions in the IO Monad, as is
the status quo, but in this case the implementation needs to be sure
that code has no side effects before it can be reorder, so ensuring
that the code also throws no exceptions is no additional hardship.
Also in general the expectation is that compilers won't be able to do
much reordering of code using the IO Monad, so even if it did inhibit
reordering a little, this would be no great loss.

So, to reconsider our options, there are basically four choices:

(a) status quo

(b) add nondetermistic exceptions

This could be done using either the NDSet based interface I
suggested, or using the (less expressive) one with
catch/handle in the IO Monad that Simon Peyton-Jones
suggested here and which Alistair Reid reported was
basically the same as is currently implemented in Hugs.

The main disadvantage of this approach is that whether
or not a program terminates becomes nondeterministic.
In addition, a minor disadvantage

Re: FW: Exceptions are too return values!

1998-06-12 Thread Alastair Reid


[EMAIL PROTECTED] (Carl R. Witty) writes:
> And I agree with this list, except for infinite loops.  How will
> exceptions help make a program robust that otherwise might loop?

Use timeouts - the poor man's solution to the halting problem.

Alastair





Re: FW: Exceptions are too return values!

1998-06-12 Thread Carl R. Witty

Alastair Reid <[EMAIL PROTECTED]> writes:

> But some of us have to write programs that keep working.  For example, 
> I'm busy hacking on our Robo-Haskell code at the moment - it just isn't
> acceptable for that kind of code to print an error message and halt.
> I remain convinced that:
> 
>   Haskell will remain a toy language until it can be used to write
>   robust programs.

I agree.

> As far as I can see, that means we either have to eliminate pattern
>  match failure, the error function, heap overflow, stack overflow
>  and infinite loops or we have to add exception handling in some form.

And I agree with this list, except for infinite loops.  How will
exceptions help make a program robust that otherwise might loop?

Carl Witty
[EMAIL PROTECTED]





Re: FW: Exceptions are too return values!

1998-06-12 Thread Alastair Reid


Fergus Henderson <[EMAIL PROTECTED]> points out that our exception handling
scheme hits problems if you hit an infinite loop instead of an exception.

Yes, this is a problem - and not a pretty one.

Fixes:

1) Remove fixpoints so that infinite loops don't happen.

   Ok, so this isn't really an option - but it's worth mentioning
   because even this isn't enough!  The problem is that our 
   optimiser might rearrange code so that we run out of heap
   instead of hitting an error.

2) Solve the halting problem.

   See (1).

3) Add timeouts (and ctrl-C handling) into the mix - practical
   approximations to solving the halting problem.

   Actually, all we really need is Concurrent Haskell and the ability
   to kill threads.  (Being able to suspend a thread would probably 
   be useful too.)  The new GHC-Hugs runtime system will have both.


Fergus then lists a bunch of options and says:

> Of these options, I'm afraid that (a), the status quo, is looking to me
> like the best of a bad lot, albeit with (c) (i) a close second.

You're welcome to do that and we certainly aren't going to try to add
 exception handling to any kind of standard before we have lots of
 experience of how well it works in practice.
(Though it would be nice if all Haskell implementations happened to
 have a compatible "non-standard" exception handling mechanism :-) )

But some of us have to write programs that keep working.  For example, 
I'm busy hacking on our Robo-Haskell code at the moment - it just isn't
acceptable for that kind of code to print an error message and halt.
I remain convinced that:

  Haskell will remain a toy language until it can be used to write
  robust programs.

As far as I can see, that means we either have to eliminate pattern
 match failure, the error function, heap overflow, stack overflow
 and infinite loops or we have to add exception handling in some form.


Alastair





Re: FW: Exceptions are too return values!

1998-06-12 Thread Fergus Henderson

On 11-Jun-1998, Amr A Sabry <[EMAIL PROTECTED]> wrote:
> There is one aspect of Java that is relevant here:
> 
> A Java implementation is free to load and link classes in any order,
> strictly or lazily, but it MUST report exceptions as if it had loaded
> and resolved the classes lazily.
> 
> I think Haskell should have the same restriction: it would bad to
> receive different exceptions because a Haskell implementation decided
> to evaluate an argument strictly before it is needed. 
> 
> Java got that right. --Amr

Java chose to favour determinacy over efficiency.
That's a reasonable decision, but it isn't the "right" decision
for all applications.  For some applications, efficiency is
more important than determinacy.

This applies to other areas of the Java spec too, such as floating point.
floating point performance problems on some platforms such as DEC Alpha. 
The solution?  Last time I looked, I think implementations of Java for
those platforms simply didn't conform to the spec.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones

> I was keeping quiet myself, because I am planning to write
> a paper touching on this topic.  But the cat seems to be
> mostly out of the bag now, so I might as well pipe up.

I'm glad you did.  That's a neat idea.  I'm familiar
with the NDSet idea -- that's in the Hughes/O'Donnell
paper that Kevin cited.  The new thing you add is
using the NDSet for the *exceptions*, rather than
for the "main value".  (It would be hopeless for every function
that could raise an exception to get an NDSet in its result
type, and hence required NDSet ops to manipulate.)  

I'll need to think more about this.  Have you got a paper on
the way?

Simon





Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones


> Just to reiterate.  I strongly urge you to ensure consistent exception
> behavior.  As a matter of course, two different compiles should not result
> in two different programs. 

One of the wonderful things about functional languages is that they
do not prescribe the order of evaluation.  To achieve the effect you
want would require us to completely prescribe that order, with
very bad effects on efficiency.  For example, consider

f :: [Int] -> Int

Suppose that an analyser figures out that f evaluates every
element of its argument list to produce its result.  Then it
is OK for the producer of the list to evaluate those thunks
right away, rather than building thunks for f to evaluate.

But if we are required to ensure consistent choice of exception
values then we can't do that any more, because the producer
might evaluate the thunks in a different order to f.

This is a big issue for a lazy language.

I really think that the thing to do is leave it unspecified
which exception is chosen.  In practice, only changing the
compiler's optimisation level is likely to change the program's
exception behaviour.

Simon


> As a matter of course, should we assume that these extensions
> (exceptions, existentials) will become part of Haskell or are they just
> part GHC?  Will they be part of Hugs?

Hugs and GHC will be consistent.  Whether it's a feature deemed
worthy of being Officially Incorporated into Haskell is not
something we'll know for a while.  It's much more likely
to be so incorporated if its implemented and found useful, though.








Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones

> Another question: Is "handle" strict in the following argument:
> 
>   handle :: (IOError -> IO a) -> IO a -> IO a
> ^
> (meaning: will "handle f (return bottom)" be bottom?)

Good question.  No, it's not strict in that sense.

Simon





Re: FW: Exceptions are too return values!

1998-06-11 Thread Fergus Henderson

On 10-Jun-1998, S. Alexander Jacobson <[EMAIL PROTECTED]> wrote:
> On Thu, 11 Jun 1998, Fergus Henderson wrote:
> > > It would make debugging easier if the exception picked was consistent
> > > accross implementations.  It doesn't matter which one, but it does matter
> > > that it is the same.  (maybe you require that Exceptions implement Ord, 
> > > or sort based on the Hashvalue of the constructor)
> > 
> > I think this would be difficult to implement efficiently.
> 
> Why is this difficult to implement efficiently?  If exceptions are strings
> (as they appear to be in Simon's initial proposal), then you can sort
> alphabetically.  If they have type, then they would be required to  
> implement Has_HashValue and the implementation could rely on existential
> types to sort.  I am sure there are better ways, but It is not obvious why
> the objection to cannonical ordering should be implementation
> efficiency...

Efficient implementations may be possible, I just don't think they are easy.

The problem is not the cost of the comparisons -- after all, that only
occurs in the exceptional case.  The problem I'm worried about is the code
size and run time cost of installing the handler in the first place.
For many common implementation models, every function such as `+' that
is strict in two or more arguments will need to install an exception handler.
This could be significant overhead, and furthermore it is overhead that
you will pay even if your program doesn't make use of exceptions.

Suppose, for argument's sake, that you are compiling to Java.
Then the code for integer plus might look something like this

int plus(HaskellInt arg1, HaskellInt arg2) {
try {
int arg1_val = arg1.eval();
} catch (Exception e1) {
try {
int arg2_val = arg2.eval();
} catch (Exception e2) {
throw (e1 < e2) ? e1 : e2;
}
throw e1;
}
int arg2_val = arg2.eval();
return arg1_val + arg2_val;
}

whereas with the nondeterministic model the code could be just

int plus(HaskellInt arg1, HaskellInt arg2) {
int arg1_val = arg1.eval();
int arg2_val = arg2.eval();
return arg1_val + arg2_val;
}

The latter will be cheaper, and the difference may be significant.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: FW: Exceptions are too return values!

1998-06-11 Thread Amr A Sabry

> One of the wonderful things about functional languages is that they
> do not prescribe the order of evaluation.  To achieve the effect you
> want would require us to completely prescribe that order, with very
> bad effects on efficiency.  For example, consider
> ...
> But if we are required to ensure consistent choice of exception
> values then we can't do that any more, because the producer
> might evaluate the thunks in a different order to f.

There is one aspect of Java that is relevant here:

A Java implementation is free to load and link classes in any order,
strictly or lazily, but it MUST report exceptions as if it had loaded
and resolved the classes lazily.

I think Haskell should have the same restriction: it would bad to
receive different exceptions because a Haskell implementation decided
to evaluate an argument strictly before it is needed. 

Java got that right. --Amr





Re: FW: Exceptions are too return values!

1998-06-11 Thread Fergus Henderson

On 10-Jun-1998, S. Alexander Jacobson <[EMAIL PROTECTED]> wrote:
> This sounds like what I wanted.  Just a few questions:
> > * A value of Haskell type T can be
> > EITHER one of the values we know and love 
> >(bottom, or constructor, or function,
> > depending on T),
> > 
> > OR it can be a set of exceptional values.
> 
> > * raise :: String -> a
> >   (raise s) returns a single exceptional value, named by string s
> 
> I presume that the programmer does not need to declare that a function
> may throw an exception ...

Correct.

> that it is inferred from the "raise" in the function.

The idea is that *any* function may potentially throw an exception.

> Furthermore, I assume that you can use the return value in
> another function without unwrapping it e.g.

Also correct.

> > * All strict operations (case, +, etc) return the union of
> >   the exceptional values returned by their strict arguments
> >   For example, if both arguments to "+" return an exceptional value
> >   then "+" returns both. Similarly, any strict context.  
> 
> It would make debugging easier if the exception picked was consistent
> accross implementations.  It doesn't matter which one, but it does matter
> that it is the same.  (maybe you require that Exceptions implement Ord, 
> or sort based on the Hashvalue of the constructor)

I think this would be difficult to implement efficiently.

Another possibility would be to specify that the exception returned
is the first one that would occur if the program is evaluated in
according to some particular order of computation.  This would be
easy to implement efficiently.  But it would break commutativity
of `+' and similar operators.  It would make it difficult for
implementations to evaluate programs in any order other than that
specified.  This might make it signficantly more difficult for
implementations to do things like automatically parallelize programs.

For Mercury, for which similar issues arise, we went with a compromise:
implementations are allowed to evaluate things in any order,
but they must also provide a way for the user to request that things
be evaluated strictly left-to-right.  This allows the user to choose
which is more important to them: efficiency or ease of debugging.

> > The neat thing about this is that the exceptions can
> > be *raised* in arbitrary purely functional code, without
> > violating referential transparency.  The question of
> > which exception is chosen is done in the IO monad, where
> > of course it is allowed to be non-deterministic.
> 
> If you can do the above and you can stay consistent about which exceptions
> you return then you should be able to catch exceptions in arbitrary purely
> function code as well, right?

If you used some canonical ordering on exceptions, then yes.
But as I said above, I think that would be difficult to implement
efficiently.

The approach using an `NDSet' monad that I outlined in another post
allows you to catch exceptions in arbitrary purely functional code,
and is much easier to implement efficienctly.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: FW: Exceptions are too return values!

1998-06-11 Thread Fergus Henderson

On 10-Jun-1998, Simon L Peyton Jones <[EMAIL PROTECTED]> wrote:
| 
| Alastair Reid has been very quiet, so I'll pipe up for him.

I was keeping quiet myself, because I am planning to write
a paper touching on this topic.  But the cat seems to be
mostly out of the bag now, so I might as well pipe up.
(Has Reid or anyone else published anything on this topic recently?)

| Here's a reasonable design for exceptions in Haskell:
...
| * raise :: String -> a
| * handle :: (String -> IO a) -> IO a -> IO a

You can do better than this.

In particular, `handle' need not be dependent on the IO monad.
You can use a seperate "nondetermistic set" monad for committed
choice nondeterminism.

>   module NDSet (
>   NDSet,
>   ndset_singleton, ndset_union, ndset_set_union, ndset_map,
>   ndset_throw, ndset_catch, ndset_handle, ndset_choose,
>   handle, throw,
>   unsafe_promise_singleton
>   ) where
>
>   -- type NDSet t
>   ndset_singleton :: t -> NDSet t
>   ndset_union :: NDSet t -> NDSet t -> NDSet t
>   ndset_set_union :: NDSet (NDSet t) -> NDSet t
>   ndset_map :: (t1 -> t2) -> NDSet t1 -> NDSet t2
>
>   instance Monad NDSet where
>   return = ndset_singleton
>   set >>= action = ndset_set_union (ndset_map action set)

The type `NDSet t' represents a set of values of type `t'.
However, the interface does not let you get at more than one
nondeterministically chosen element from the set, so the
implementation of the type only stores a single element.

This type is useful for committed choice nondeterminism in general,
and exceptions in particular:

>   type Exception = IOError-- or String, etc.
>   data MaybeException t = OK t | GotException (NDSet Exception)
>   ndset_throw :: (NDSet Exception) -> any
>   ndset_catch :: t -> MaybeException t

This allows you to establish handlers in the
functional part of the code which does not have access to the IO monad.
Such code can catch exceptions, and then may at its option
ignore them, rethrow them, rethrow different exceptions,
store the exceptions in data structures (as values of type `NDSet Exception'),
and so forth.  However, you can't get at individual exceptions,
you can only apply functions to sets of exceptions.

Only once you get back to the IO monad can you select an individual exception:

>   ndset_choose :: IO (NDSet t) -> IO t

The `handle' and `throw' that you suggested can be implemented in terms
of these `ndset_throw', `ndset_catch', and `ndset_choose':

>   throw :: Exception -> any
>   throw e = ndset_throw (ndset_singleton e)
>
>   ndset_handle :: (Exception -> t) -> t -> NDSet t
>   ndset_handle handler value =
>   case (ndset_catch value) of
>   OK value -> ndset_singleton value
>   GotException exception_vals ->
>   ndset_map handler exception_vals

>   handle :: (Exception -> IO a) -> IO a -> IO a
>   handle handler action = do
>next_action <- ndset_choose (return (ndset_handle handler action))
>next_action

In addition, the following primitive is very useful:

>   unsafe_promise_singleton :: NDSet t -> t
>   unsafe_promise_singleton s = unsafePerformIO (ndset_choose (return s))

The idea of this primitive is that the user is promising that the NDSet
in question is a singleton set; they can then get back the single
element.  This primitive is unsafe in general, but it can be used in
ways that are guaranteed to be safe.  For example, if only care about
whether you got an exception, not about what exception you got, you can
use the following:

>   -- `simple_handle x' returns `Nothing', if evaluation of `x' throws
>   -- an exception, or `Just x' otherwise.
>   simple_handle :: a -> Maybe a
>   simple_handle x = unsafe_promise_singleton (
>   ndset_handle (\ exception -> Nothing) (Just x))

Because we map all exceptions to `Nothing', and because a function
is guaranteed to either return a set of exceptions or return a value,
but not both, the set of values returned from the call to `ndset_handle'
is guaranteed to be either { Nothing } or { Just x }, and in either
case this is a singleton set, so it's safe to call `unsafe_promise_singleton'.

This is not a good example, because you can get the same effect more
simply using `ndset_catch' instead of `ndset_handle'.  Offhand,
I couldn't think of any good examples of its use with exceptions. 
However, `unsafe_promise_singleton' is definitely useful when NDSets
for things other than exceptions.

The implementation of most of this is quite straightforward:

>   newtype NDSet s = MakeNDSet s
>
>   ndset_singleton x = MakeNDSet x
>   ndset_union x y = x
>   ndset_set_union (MakeNDSet x) = x
>   ndset_map f (MakeNDSet x) = MakeNDSet (f x)
>
>   ndset_choose ndaction = do
>   Ma

Re: FW: Exceptions are too return values!

1998-06-10 Thread Kevin Hammond

At 2:40 pm 10/6/98, Simon L Peyton Jones wrote:
>Here's a reasonable design for exceptions in Haskell:
>
>* A value of Haskell type T can be
>EITHER one of the values we know and love
>   (bottom, or constructor, or function,
>depending on T),
>
>OR it can be a set of exceptional values.

>I'd be interested to know what people think of this.

The error values and raising are similar to my PhD thesis (the type
domains weren't a big problem -- it's technically straightforward [though
perhaps philosophically debatable] to add additional values to a domain if
you wish,
and preserve these through other domains)!  [For the record, this was in an
early SML,
and the current SML design is broadly similar to this, but with extendible
exceptions (and a fixed evaluation order) as Ralf Hinze notes].
The non-deterministic handling is interesting and eliminating
the error checks is a good thing, of course.

One issue in my system was what to do for partial applications (do they return
an exception instantly or only when fully applied -- I suppose in this setting
you return the union of the possibilities and do whatever's convenient
in the implementation).  You also have to worry about what to when an exception
raises an exception when you try to look at it in the handler (probably raised
to a higher-level rather than handled locally).  A parallel setting (one of
my PhD motivations) would need a little care to avoid invoking the same handler
multiple times if several threads raised exceptions.

One thing you haven't noted:  doesn't this also work for user interrupts
too (Control-C)
-- presumably there's no reason why it shouldn't (it did in my setting).

Incidentally, why have you put the handler first?  It stops you writing

e `handle` h

as with catch, and I'd expect would make it a bit harder to convert code?

Regards,
Kevin

--
Division of Computer Science,   Tel: +44-1334 463241 (Direct)
School of Mathematical  Fax: +44-1334 463278
 and Computational Sciences,URL:
http://www.dcs.st-and.ac.uk/~kh/kh.html
University of St. Andrews, Fife, KY16 9SS.






Re: FW: Exceptions are too return values!

1998-06-10 Thread Koen Claessen

On Wed, 10 Jun 1998, Simon L Peyton Jones wrote:

 | We're implementing an experimental version of this
 | in GHC, integrated with the IO monad exceptions, so that
 | 
 |   handle :: (IOError -> IO a) -> IO a -> IO a
 | 
 | and we add an extra constructor (UserError String) to the
 | IOError type for exceptions raised by raise.

How about adding the following errors:

  data IOError
= ...
| HeapOverflowError
| StackOverflowError

This is very useful when you for example want to implement a Hugs like
system in Haskell.

Now your Haskell programs will be very unlikely to crash!

Another question: Is "handle" strict in the following argument:

  handle :: (IOError -> IO a) -> IO a -> IO a
^
(meaning: will "handle f (return bottom)" be bottom?)

Regards,
Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.





Re: FW: Exceptions are too return values!

1998-06-10 Thread Alastair Reid


Simon L Peyton Jones <[EMAIL PROTECTED]> writes:
> Alastair Reid has been very quiet, [...]

Sorry about that - I just got back from a trip to Germany and am still
 trying to catch up on my mail, get the June 98 (bugfix) release of Hugs
 out the door, etc.

Exception handling has been high on "Why Haskell is a toy language" list
 for quite a while now - so I'm very happy that Hugs, GHC and HBC will
 all provide exception handling.


"S. Alexander Jacobson" <[EMAIL PROTECTED]> writes:
> As a matter of course, should we assume that these extensions
> (exceptions, existentials) will become part of Haskell or are they just
> part GHC?  Will they be part of Hugs?

Hugs has had catchError (which is essentially the same as catch#)
for over a year now.  We added it when we created the Graphics
library because we had to make sure that graphics programs 
cleaned up after themselves even if they hit a pattern match error.
We'll replace/supplement catchError with catch in due course.

Existentials (and all the other goodies in Hugs 1.3c) will not be
 in the June 98 Hugs release - but ought to be in the next one.
(Sorry about this - we're busy working on the Hugs-GHC merger,
 generating deliverables for our funding bodies, putting
 together new funding proposals, adding exception handling to
 GHC, etc, etc.  If someone could make a couple of clones of
 Mark Jones or myself...)


Ralf Hinze <[EMAIL PROTECTED]> writes:
> The fact that the type of exceptions is fixed (`String' or `IOError')
> is a weak point of the design (compared to Standard ML).

This weakness is almost a design feature.  Given the non-determinism
in which exception is raised in a program like this:

  print ( (1 `div` 0) + (head []) )

we really don't recommend the construction of elaborate exception handlers
that try to figure out which exception was raised (as one might in Java
or ML).

That said, I've felt for a while thatthe fixed nature of the IOError type
 was going to be a problem as we added new "actions" (such as openWindow
 or sendEMail) to the IO monad.  GreenCard 1 (but sadly not GC 2) allowed
 you define new constructors for the IOError type.  Given a declaration
 (something) like this:

  %exception Foo :: Int -> String -> IOError

it defined a function to construct an exception and a function to test 
for an exception:

  mkFoo :: Int -> String -> IOError
  isFoo :: IOError -> Maybe (Int,String)


Koen Claessen <[EMAIL PROTECTED]> writes:
> How about adding the following errors:
> 
>   data IOError
> = ...
> | HeapOverflowError
> | StackOverflowError
> 
> This is very useful when you for example want to implement a Hugs like
> system in Haskell.

Resource overflows (like timeouts and ctrl-C) are very different
beasts from pattern match failure and calls to error.
The main difference is that 

  1 `div` 0

always raises an exception - irrespective of what else is going on at the 
time.  If you evaluate 1 `div` 0 some other time, you'll still get an 
exception.  On the other hand, a large, stack and space hungry expression
like 

  sum [1..100]

might run out of heap/stack or may evaluate just fine depending on 
a whole bunch of factors - even within the same run of the program.

The first kind of error has a tolerably straightforward domain theoretic
semantics (see Lennart's hbi paper for a first approximation) whereas
resource overflow errors can only be described in an operational semantics.

In the implementation, this difference manifests itself in things like
being able to revert black holes to their former state (but without the
space leak or duplicated work of a naive implementation) and other
such tweaking.

So they're different things, but since they're an essential part of trying
to lift Haskell out of Toyland, we will be doing it - possibly with the
interface you suggest.  Stay tuned to the Hugs and GHC mailing lists...


"S. Alexander Jacobson" <[EMAIL PROTECTED]> writes:
> It would make debugging easier if the exception picked was consistent
> across implementations.  

The semantics given doesn't even guarantee that you'll get the same exception
from the same implementation.  Indeed, the same expression could even
raise different exceptions each time you evaluate it (though the
current implementation won't do this).

This "flaw" keeps the implementation simple and efficient because
it means that we can stop evaluating an expression and jump to the
handler the moment we hit the first raise#.All that talk of
sets of errors is just a semantic device to restrict the
non-determinism to the IO monad instead of letting it pollute the
whole system.  (The idea is based on the Hughes-O'Donnell non-determinism
monad [1].)

Fixing this flaw would mean we'd have to keep evaluating even after we
hit the first error.  This has two big problems:

1) I don't know how to implement it. :-)
2) If all you care about is that an error happened and that you can
   print an error message on the screen or in a log file or whate

Re: FW: Exceptions are too return values!

1998-06-10 Thread S. Alexander Jacobson

On Thu, 11 Jun 1998, Fergus Henderson wrote:
> > It would make debugging easier if the exception picked was consistent
> > accross implementations.  It doesn't matter which one, but it does matter
> > that it is the same.  (maybe you require that Exceptions implement Ord, 
> > or sort based on the Hashvalue of the constructor)
> 
> I think this would be difficult to implement efficiently.

Why is this difficult to implement efficiently?  If exceptions are strings
(as they appear to be in Simon's initial proposal), then you can sort
alphabetically.  If they have type, then they would be required to  
implement Has_HashValue and the implementation could rely on existential
types to sort.  I am sure there are better ways, but It is not obvious why
the objection to cannonical ordering should be implementation
efficiency...

-Alex-

___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax






Re: FW: Exceptions are too return values!

1998-06-10 Thread Tommy Thorn

Thats a wonderful idea.  With that it will be so much easier to write
robust code without bloating the code with error checks.

I've always been annoyed that I couldn't trap arbitrary errors, say to
close down the application cleanly.

Now, we only need extendible data types, and then we have an (almost)
ML-like exception system :)

/Tommy

Simon L Peyton Jones wrote/a ecrit/skrev:
> 
> Alastair Reid has been very quiet, so I'll pipe up for him.
> 
> Here's a reasonable design for exceptions in Haskell:
> 
> * A value of Haskell type T can be
>   EITHER one of the values we know and love 
>  (bottom, or constructor, or function,
>   depending on T),
> 
>   OR it can be a set of exceptional values.
> 
> * raise :: String -> a
>   (raise s) returns a single exceptional value, named by string s
> 
> * All strict operations (case, +, etc) return the union of
>   the exceptional values returned by their strict arguments
>   For example, if both arguments to "+" return an exceptional value
>   then "+" returns both. Similarly, any strict context.  
> 
> * handle :: (String -> IO a) -> IO a -> IO a
>   (handle h a) tries to perform the action a.
>   If doing so delivers a set of exceptional values then
>   apply the exception handler h to the string that names
>   one of them.  It is not defined which of the exceptional 
>   values is picked.
> 
> 
> The neat thing about this is that the exceptions can
> be *raised* in arbitrary purely functional code, without
> violating referential transparency.  The question of
> which exception is chosen is done in the IO monad, where
> of course it is allowed to be non-deterministic.
> The implementation does not keep sets of exceptional values,
> of course.  It simply propagates the first one it trips
> over to the nearest enclosing handler.
> 
> (It is likely that successive runs will actually give
> the same behaviour, but recompiling the program with
> (say) different optimisation levels might change the order
> of evaluation, and hence change which exception is tripped
> over first.)
> 
> We're implementing an experimental version of this
> in GHC, integrated with the IO monad exceptions, so that
> 
>   handle :: (IOError -> IO a) -> IO a -> IO a
> 
> and we add an extra constructor (UserError String) to the
> IOError type for exceptions raised by raise.
> 
> Calls to "error" also show up as an exceptional value, of
> course.
> 
> One merit of the system is that it chops out a tremendous
> number of run-time error checks in the IO monad, since
> we are now free to implement the mechanism with standard
> stack-unwinding techniques.  Result: much better I/O performance.
> 
> 
> I'd be interested to know what people think of this.
> 
> Simon





Re: FW: Exceptions are too return values!

1998-06-10 Thread Ralf Hinze

> I'd be interested to know what people think of this.

> Here's a reasonable design for exceptions in Haskell:
> ...
> The neat thing about this is that the exceptions can
> be *raised* in arbitrary purely functional code, without
> violating referential transparency.  The question of
> which exception is chosen is done in the IO monad, where
> of course it is allowed to be non-deterministic.
> The implementation does not keep sets of exceptional values,
> of course.  It simply propagates the first one it trips
> over to the nearest enclosing handler.

That's neat indeed. What is especially nice is the ability
to catch `error' exceptions.

> We're implementing an experimental version of this
> in GHC, integrated with the IO monad exceptions, so that
> 
>   handle :: (IOError -> IO a) -> IO a -> IO a
> 
> and we add an extra constructor (UserError String) to the
> IOError type for exceptions raised by raise).

The fact that the type of exceptions is fixed (`String' or `IOError')
is a weak point of the design (compared to Standard ML). It forces the
programmer to encode exceptions as strings which is not what I would
call elegant. [I weakly recall that there was a discussion on this
point some years ago.] However, I see no way to improve the design :-(
other than extending Haskell (with extensible sum types a la SML's
`exception' declaration).

> One merit of the system is that it chops out a tremendous
> number of run-time error checks in the IO monad, since
> we are now free to implement the mechanism with standard
> stack-unwinding techniques.  Result: much better I/O performance.

I love performance gains ;-).

Cheer, Ralf





Re: FW: Exceptions are too return values!

1998-06-10 Thread Lennart Augustsson


> * raise :: String -> a
> * handle :: (String -> IO a) -> IO a -> IO a
> I'd be interested to know what people think of this.
I like the trick of handle being in the IO monad to avoid
problems with evaluation order.  As usual though, it can be a 
high price to pay if all you wanted was a little local
error handling.

I'll probably add it to hbc.

-- Lennart





Re: FW: Exceptions are too return values!

1998-06-10 Thread Simon L Peyton Jones


Alastair Reid has been very quiet, so I'll pipe up for him.

Here's a reasonable design for exceptions in Haskell:

* A value of Haskell type T can be
EITHER one of the values we know and love 
   (bottom, or constructor, or function,
depending on T),

OR it can be a set of exceptional values.

* raise :: String -> a
  (raise s) returns a single exceptional value, named by string s

* All strict operations (case, +, etc) return the union of
  the exceptional values returned by their strict arguments
  For example, if both arguments to "+" return an exceptional value
  then "+" returns both. Similarly, any strict context.  

* handle :: (String -> IO a) -> IO a -> IO a
  (handle h a) tries to perform the action a.
  If doing so delivers a set of exceptional values then
  apply the exception handler h to the string that names
  one of them.  It is not defined which of the exceptional 
  values is picked.


The neat thing about this is that the exceptions can
be *raised* in arbitrary purely functional code, without
violating referential transparency.  The question of
which exception is chosen is done in the IO monad, where
of course it is allowed to be non-deterministic.
The implementation does not keep sets of exceptional values,
of course.  It simply propagates the first one it trips
over to the nearest enclosing handler.

(It is likely that successive runs will actually give
the same behaviour, but recompiling the program with
(say) different optimisation levels might change the order
of evaluation, and hence change which exception is tripped
over first.)

We're implementing an experimental version of this
in GHC, integrated with the IO monad exceptions, so that

handle :: (IOError -> IO a) -> IO a -> IO a

and we add an extra constructor (UserError String) to the
IOError type for exceptions raised by raise.

Calls to "error" also show up as an exceptional value, of
course.

One merit of the system is that it chops out a tremendous
number of run-time error checks in the IO monad, since
we are now free to implement the mechanism with standard
stack-unwinding techniques.  Result: much better I/O performance.


I'd be interested to know what people think of this.

Simon






Re: FW: Exceptions are too return values!

1998-06-10 Thread S. Alexander Jacobson

Simon and Alastair,

This sounds like what I wanted.  Just a few questions:
> * A value of Haskell type T can be
>   EITHER one of the values we know and love 
>  (bottom, or constructor, or function,
>   depending on T),
> 
>   OR it can be a set of exceptional values.

> * raise :: String -> a
>   (raise s) returns a single exceptional value, named by string s

I presume that the programmer does not need to declare that a function
may throw an exception ... that it is inferred from the "raise" in the
function.  Furthermore, I assume that you can use the return value in
another function without unwrapping it e.g.

divide x y = if y==0 then raise DivideByZeroException
divideCaller x y = 1.0 + (divide x y)

Could you give a code example to clarify if I am mistaken?
 
> * All strict operations (case, +, etc) return the union of
>   the exceptional values returned by their strict arguments
>   For example, if both arguments to "+" return an exceptional value
>   then "+" returns both. Similarly, any strict context.  

It would make debugging easier if the exception picked was consistent
accross implementations.  It doesn't matter which one, but it does matter
that it is the same.  (maybe you require that Exceptions implement Ord, 
or sort based on the Hashvalue of the constructor)

> * handle :: (String -> IO a) -> IO a -> IO a
>   (handle h a) tries to perform the action a.
>   If doing so delivers a set of exceptional values then
>   apply the exception handler h to the string that names
>   one of them.  It is not defined which of the exceptional 
>   values is picked.

As noted above, there should be some cannonical order.
But, again I am having a little trouble understanding what you are saying
here.  Can you give some example code?

Also, why do you have String here?  Why can't exceptions be typed like in
Java?  Maybe exceptions should be a class and you use existential types...
(I just read a paper on polytypic functions last night...maybe those?)

> The neat thing about this is that the exceptions can
> be *raised* in arbitrary purely functional code, without
> violating referential transparency.  The question of
> which exception is chosen is done in the IO monad, where
> of course it is allowed to be non-deterministic.

If you can do the above and you can stay consistent about which exceptions
you return then you should be able to catch exceptions in arbitrary purely
function code as well, right?
(yes, I know I am changing positions again, but I am still learning).  

> (It is likely that successive runs will actually give
> the same behaviour, but recompiling the program with
> (say) different optimisation levels might change the order
> of evaluation, and hence change which exception is tripped
> over first.)

Just to reiterate.  I strongly urge you to ensure consistent exception
behavior.  As a matter of course, two different compiles should not result
in two different programs.  When you distribute your program to users,
add features, and distribute again, you don't want to diagnose the same
problem in two different ways in two different versions.  It makes
customer service just that much harder.

> We're implementing an experimental version of this
> in GHC, integrated with the IO monad exceptions, so that

As a matter of course, should we assume that these extensions
(exceptions, existentials) will become part of Haskell or are they just
part GHC?  Will they be part of Hugs?
 
-Alex-
___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax