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 is that the actual
            exceptions thrown are nondeterministic.  (This itself
            could of course lead to nondeterminism re termination,
            but that is much less likely and much easier to detect
            and to control than nontermination due to exceptions
            not being raised early enough.)

        (c) add deterministic exceptions
        
            This could be done either using either an interface
            like the one I suggested but with Sets instead of NDSets,
            or using one that just returns a single exception,
            or using aforementioned ones with catch in the IO Monad,
            but with the semantics tightened to specify exactly
            which exception is returned.

            This has the disadvantage that it inhibits the use
            of reordering optimizations, except for cases where the
            compiler can prove that the relevant subexpressions
            cannot throw any exceptions.  This would be a great
            pity, since the supposed ease of doing these kind of
            optimizations was one of the great motivations for
            pure functional programming in the first place.
            (Not the only one, for sure, but certainly one of
            the major ones.)

            There are two sub-cases:

            (i) not preserving commutativity of `+'

                This of course has the disadvantage that certain
                "standard" rules of mathematics no longer apply.

            (ii) preserving commutativity of `+' and similar operations

                For this case, if you're returning a single exception
                then for operations such as `+' you need to compute
                the set of exceptions raised and then return the
                least element of that set, according to some
                canonical ordering.

                The disadvantage is that the need to compute the
                set of exceptions raised may cause time and/or space
                overheads (due to the need to setup additional 
                exception handlers) and/or increase implementation
                complexity.

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.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]        |     -- the last words of T. S. Garp.


Reply via email to