
Hi all, Proposal: http://hackage.haskell.org/trac/ghc/ticket/1239 Consider: let n = 0/0 :: Double in (n `compare` n, n < n, n == n, n > n) In GHC and YHC this gives (GT,False,False,False) while in hugs it gives (EQ,False,False,False) Neither of these is very satisfactory, as I would expect x `compare` y === EQ => (x == y) === True x `compare` y === GT => (x > y) === True and it's even less pleasant that the implementations differ for no good reason. The Haskell report isn't very helpful on how comparing exceptional Doubles should behave, as it doesn't even say you need to have NaN etc: http://haskell.org/onlinereport/basic.html#sect6.4 The results of exceptional conditions (such as overflow or underflow) on the fixed-precision numeric types are undefined; an implementation may choose error (_|_, semantically), a truncated value, or a special value such as infinity, indefinite, etc. I think that the right answer is that n `compare` n above (and more generally such a comparison for any incomparable Doubles or Floats) should raise an error (i.e. be _|_). The changes needed are simple, e.g. for GHC (D# x) `compare` (D# y) | x <## y = LT | x ==## y = EQ | otherwise = GT becomes (D# x) `compare` (D# y) | x <## y = LT | x ==## y = EQ | x >## y = GT | otherwise = error "Incomparable values" Deadline: 1 week after discussion ends. Thanks Ian

Ian Lynagh
(D# x) `compare` (D# y) | x <## y = LT | x ==## y = EQ | otherwise = GT
becomes
(D# x) `compare` (D# y) | x <## y = LT | x ==## y = EQ | x >## y = GT | otherwise = error "Incomparable values"
I'm pretty uncomfortable with calling 'error' in this situation. How about throwing an imprecise exception instead? Regards, Malcolm

On Tue, Mar 20, 2007 at 03:53:58PM +0000, Malcolm Wallace wrote:
Ian Lynagh
wrote: (D# x) `compare` (D# y) | x <## y = LT | x ==## y = EQ | otherwise = GT
becomes
(D# x) `compare` (D# y) | x <## y = LT | x ==## y = EQ | x >## y = GT | otherwise = error "Incomparable values"
I'm pretty uncomfortable with calling 'error' in this situation. How about throwing an imprecise exception instead?
Doesn't error throw an imprecise exception? We already have things like remInteger ia ib | ib == 0 = error "Prelude.Integral.rem{Integer}: divide by 0" We could throw (ArithException something) instead if that's what you mean, but I think we'd need a new constructor for something. I'm not sure if it should be an ArithException or not. (should remInteger above throw (ArithException DivideByZero)? We'd give a less useful message to the developer, but have something possibly more useful to catch. I've wished for exceptions to have a stack of locations in the past; perhaps that should be another proposal.) Thanks Ian

On Tuesday 20 March 2007 16:22, Ian Lynagh wrote:
Proposal: http://hackage.haskell.org/trac/ghc/ticket/1239
Consider:
let n = 0/0 :: Double in (n `compare` n, n < n, n == n, n > n)
In GHC and YHC this gives
(GT,False,False,False)
while in hugs it gives
(EQ,False,False,False)
Neither of these is very satisfactory, as I would expect [...]
I think all 'False' are very satisfactory, at least when one is expecting IEEE behaviour. The only real problem is the Ordering part: The Haskell 98 report explicititly states that "The Ord class is used for totally ordered datatype". Obviously, this excludes IEEE floating point numbers, which are *not* totally ordered. So what can we do here? * Throw an exception when 'compare' sees a NaN: This gives me a rather bad feeling, because all other floating point operations I'm aware of in all current Haskell implementations do not throw any exception. Of course the Haskell 98 report is extremely vague about this and would allow throwing an exception, but a fundamental difference between (<), (>), ... and 'compare' would not be nice. * Disallow 'instance Ord Float' and 'instance Ord Double': This would contradict the report. * Let (<), (>), ... throw an exception for NaN, too: Allowed by the report, too, but this would surprise even more people. Furthermore, those operations couldn't be mapped directly to IEEE processor operations anymore. * Fix the Haskell report somehow: I think that in the long run this would be the best solution. Either Ordering would get a fourth alternative for uncomparable values, or some words of warning should be added to the description of the Ord class. What's the status of Haskell' regarding floating point operations? Other languages like e.g. Java are very specific about this topic, but this comes at a price (e.g. logical negation does not distribute over floating point relational operations anymore). I propose to leave implementations as they are currently, following the TITO principle ("trash in, trash out"). BTW, OpenGL explicitly states that *no* operation leads to OpenGL interruption or termination, even if NaN, infinities, etc. are involved. The operations are just undefined in the latter cases. So we would be in good company then... :-) Cheers, S.

Hi
Neither of these is very satisfactory, as I would expect [...]
And _|_ is perhaps the least satisfactory value of them all! Following on from the tradition of ByteString, will it be acceptable for the compiler to turn _|_ into False, as an optimisation? I agree very much with Sven here, nothing as simple as comparison or equality should make a program crash. I wouldn't mind division by zero raising an error - that is something that you could argue for. Given that Ord and Num operations on Double/Float don't obey lots of useful properties, due to rounding, perhaps we should just make it clear (somewhere) that floating point numbers aren't nice things to work with, and should be avoided when an Integer will do fine. Maybe thats already implicit in most programmers heads though, so doesn't even need stating. Thanks Neil

On 21/03/07, Neil Mitchell
Following on from the tradition of ByteString, will it be acceptable for the compiler to turn _|_ into False, as an optimisation?
My interpretation of Ian's message was a questioning of the behaviour of compare, not of (<) etc. compare can't return False.
I agree very much with Sven here, nothing as simple as comparison or equality should make a program crash. I wouldn't mind division by zero raising an error - that is something that you could argue for.
Doesn't compare need to force its arguments anyway, so that (0/0) `compare` (0/0) would be a divide-by-zero error? -- -David House, dmhouse@gmail.com

On Wed, Mar 21, 2007 at 06:58:46PM +0000, David House wrote:
On 21/03/07, Neil Mitchell
wrote: Following on from the tradition of ByteString, will it be acceptable for the compiler to turn _|_ into False, as an optimisation?
My interpretation of Ian's message was a questioning of the behaviour of compare, not of (<) etc. compare can't return False.
Right, I'm happy with the three False's, it's the incompatible result of compare that I'm objecting to. As Sven thinks the real solution is to modify the report such that this case can be handled nicely without raising an exception, I've closed the proposal and opened a Haskell' ticket for it. Thus we can discuss what the answer should be for Haskell' and change the report or not as we think appropriate, before finally fixing the problem. http://hackage.haskell.org/trac/haskell-prime/ticket/123
I agree very much with Sven here, nothing as simple as comparison or equality should make a program crash. I wouldn't mind division by zero raising an error - that is something that you could argue for.
Doesn't compare need to force its arguments anyway, so that (0/0) `compare` (0/0) would be a divide-by-zero error?
Not with Float and Double: Prelude> 0/0 :: Double NaN Prelude> 0/0 :: Float NaN Thanks Ian

Hi
My interpretation of Ian's message was a questioning of the behaviour of compare, not of (<) etc. compare can't return False.
Right, I'm happy with the three False's, it's the incompatible result of compare that I'm objecting to.
My main point was the question of whether compilers are free to optimise _|_ to a concrete (non-nonsensical) value. If so this proposal can be treated as a no-op by compilers that do. I'm still not happy with adding more incompleteness into something that intuitively feels safe - compare is pretty benign. Having a crash on division is something that does appeal to me more. For reference, my Catch tool treats Float/Double compare as never crashing, and division by zero as always crashing - which I find more intuitive. Thanks Neil

I'm still not happy with adding more incompleteness into something that intuitively feels safe - compare is pretty benign. Having a crash on division is something that does appeal to me more. Are you suggesting that 0.0/0.0 should crash also? I'm no expert, but
Neil Mitchell wrote: think returning a NaN is according to the floating point standard (IEEE 754), and I'm not convinced Haskell should break that. If you use floating point, you need to know the pitfalls anyway. Maybe comparing NaNs should give random results? :-) The bad thing is that comparison can hide the NaNs (for arithmetic, NaNs will be contagious, so you'll likely get a NaN riddled output). One thing I remember seeing (from Fortran compilers?) is that when a program execution involves a NaN, it is reported on termination, even if the NaN was in an intermediate calculation and not part of the final result. Something like that could perhaps be useful if the current behavior is kept? -k

On Mar 22, 2007, at 8:21 AM, Ketil Malde wrote:
Neil Mitchell wrote:
I'm still not happy with adding more incompleteness into something that intuitively feels safe - compare is pretty benign. Having a crash on division is something that does appeal to me more. Are you suggesting that 0.0/0.0 should crash also? I'm no expert, but think returning a NaN is according to the floating point standard (IEEE 754), and I'm not convinced Haskell should break that.
IIRC, signaling NaNs (ie, throwing an error), are also allowed under IEEE 754, albeit less common. In the context of Haskell, I think it makes a lot more sense. Remove NaN as a value and Float/Double regain a total orders, and real equivalence relations (not PERs). Also, if I get a NaN in a calculation, I'd personally rather get an exception than have NaNs infect the entire computation and only find out later. Another potentially attractive option is to recast Eq as being only a PER (remove the reflexivity assumption) and allow Ord to be a partial order. Or maybe: class PEq a where { (==) (/=) :: a -> a -> Bool } class PEq a => Eq a class POrd a where { compare :: ....; (<=) :: ...; etc } class POrd a => Ord a so we introduce new classes with the relaxed semantics and make Ord/ Eq subclasses with no new operations. Although, this is obviously Haskell' territory.
If you use floating point, you need to know the pitfalls anyway. Maybe comparing NaNs should give random results? :-)
The bad thing is that comparison can hide the NaNs (for arithmetic, NaNs will be contagious, so you'll likely get a NaN riddled output). One thing I remember seeing (from Fortran compilers?) is that when a program execution involves a NaN, it is reported on termination, even if the NaN was in an intermediate calculation and not part of the final result. Something like that could perhaps be useful if the current behavior is kept?
-k
Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Ketil Malde wrote:
I'm still not happy with adding more incompleteness into something that intuitively feels safe - compare is pretty benign. Having a crash on division is something that does appeal to me more. Are you suggesting that 0.0/0.0 should crash also? I'm no expert, but
Neil Mitchell wrote: think returning a NaN is according to the floating point standard (IEEE 754), and I'm not convinced Haskell should break that. If you use floating point, you need to know the pitfalls anyway. Maybe comparing NaNs should give random results? :-)
:-) non-referential-transparency always seems attractive for silly cases like this, doesn't it
The bad thing is that comparison can hide the NaNs (for arithmetic, NaNs will be contagious, so you'll likely get a NaN riddled output).
Yes - non-signalling NaN in a pure language like Haskell is similar to _|_, with the biggest difference being that you can check whether a value is NaN/Inf/-Inf (in pure code). (where that _|_ could specifically be some sort of NaN imprecise exception). Of course _|_ is still the least fixed point, e.g. infinity = infinity + 1 won't give you an Infinity. So, do we want _some_ computations to be ill-defined in a well-behaved way by using the IEEE NaN bit-patterns as we do? The FiniteDouble wrapper seem like an interesting approach. If you don't want the CPU to do all that checking of intermediate values... but that can be optimized away anyway. What is a use case for code that wants to check whether a value is NaN? Perhaps the positive and negative infinities are more commonly worth being non-_|_ since they don't break the total order and can be generated by mere overflow (2.0^(2^1000) anyone?). Furthermore, since with a large finite double subtracting 1 does not reduce the number, is infinity that much weirder? Another approach I tried with a type for integers including +-Infinity and NaN was to just arbitrarily make NaN be less than all other values, including -Infinity, and it is a total order (other values are greater than NaN, and NaN is equal to itself). That way it can be stored in Maps and such. (I later decided I didn't really like the mathematically not-very-sensible-ness of those values existing, for my use case, but that's a different matter.) Does anyone else think (==) should always be reflexive for any type it's defined for? (i.e. for all n, (n==n)==True) (except when its arguments contain _|_, in which case (==) might inevitably result in _|_). The class "RealFloat" in the prelude already provides isNaN, isInfinite... which are more sensible than checking for NaN with not(n==n) in Haskell Isaac -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.3 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iD8DBQFGBSbdHgcxvIWYTTURAu1RAJ44waLiwdfIklbUmFyXW1CwVI2CEwCgzRBF 4wU29F5OIKCdWyK41crSX3s= =usWc -----END PGP SIGNATURE-----

On Thu, Mar 22, 2007 at 10:52:24AM +0000, Neil Mitchell wrote:
My main point was the question of whether compilers are free to optimise _|_ to a concrete (non-nonsensical) value.
No. Note that in the bytestring case the compiler doesn't do so, it's the library that does (by telling the compiler to rewrite things with RULEs). And it's very naughty for doing so, and should go to bed with no supper. Unfortunately, it's very appealing in bytestring's case...
I'm still not happy with adding more incompleteness into something that intuitively feels safe - compare is pretty benign. Having a crash on division is something that does appeal to me more.
For reference, my Catch tool treats Float/Double compare as never crashing, and division by zero as always crashing
Even for Double/Float? There's also: Prelude> (minBound :: Int) `div` (-1) *** Exception: arithmetic overflow but you probably can't do much about that in Catch. Thanks Ian

Hi
Note that in the bytestring case the compiler doesn't do so, it's the library that does (by telling the compiler to rewrite things with RULEs).
ByteString is in base, and ships with GHC, I think that makes it GHC's fault if it does naughty things.
Unfortunately, it's very appealing in bytestring's case...
Yes, the dilema between performance and purity...
For reference, my Catch tool treats Float/Double compare as never crashing, and division by zero as always crashing
Even for Double/Float?
Yes.
There's also:
Prelude> (minBound :: Int) `div` (-1) *** Exception: arithmetic overflow
but you probably can't do much about that in Catch.
There is an easy solution, always use Integers. Catch also assumes rules like adding two positive numbers results in a positive number - which unfortunately isn't actually true. Thanks Neil

On Thu, 2007-03-22 at 14:50 +0000, Neil Mitchell wrote:
Hi
Note that in the bytestring case the compiler doesn't do so, it's the library that does (by telling the compiler to rewrite things with RULEs).
ByteString is in base, and ships with GHC, I think that makes it GHC's fault if it does naughty things.
Unfortunately, it's very appealing in bytestring's case...
Yes, the dilema between performance and purity...
It's not impure. Our rewrite rules for ByteStrings can refine your code (in the domain / CPO sense) by making it lazier. It doesn't 'invent' random values to replace _|_ it gives you the result you'd have got if the data type were slightly lazier. The optimised version doesn't force things that are not necessary for calculating the result and if any of those things you would have forced were _|_ then we've done a refinement rather than a strict equality rewrite. We never rewrite in the opposite direction since that'd be bad. Duncan

I have another proposal: make different types. People who want integers have the choice of Int (or Int64, etc) for performance or Integer for stronger algebraic guarantees. I suggest Double be split into types with different guarantees: One that avoids "error" (and has weird NaN / Inf behavior) Another that avoids having or propagating NaN/Inf by always throwing an error. And perhaps an IEEE type with specific Nan/Inf behavior ? So (0.0/0.0 :: Double) is NaN and (0.0/0.0 :: FiniteDouble) is an error. The same applies to Float/FiniteFloat: newtype FiniteDouble = FiniteDouble Double newtype FiniteFloat = FiniteDouble Float Is there some reason to avoid this solution?
participants (10)
-
Chris Kuklewicz
-
David House
-
Duncan Coutts
-
Ian Lynagh
-
Isaac Dupree
-
Ketil Malde
-
Malcolm Wallace
-
Neil Mitchell
-
Robert Dockins
-
Sven Panne