Proper Handling of Exceptional IEEE Floating Point Numbers

Comparison of exceptional IEEE floating point numbers, like Nan, seems
to have some bugs in ghci (version 6.12.1).
These are correct, according to the IEEE floating point standards:
Prelude> 0 < (0/0)
False
Prelude> 0 > (0/0)
False
Prelude> 0 == (0/0)
False
But these are inconsistent with the above, and arguably incorrect:
Prelude> compare (0/0) (0/0)
GT
Prelude> compare (0/0) 0
GT
Prelude> compare 0 (0/0)
GT
Prelude> compare (0/0) (1/0)
GT
Prelude> compare (1/0) (0/0)
GT
I'd suggest that compare involving a NaN should yield
error "violation of the law of the excluded middle"
The min and max functions have strange behaviour with regard to NaN,
especially when mixed with Infinity:
Prelude> max (0/0) (1/0)
NaN
Prelude> max (1/0) (0/0)
Infinity
Prelude> min (0/0) (1/0)
Infinity
Prelude> max (0/0) 0
NaN
Prelude> max 0 (0/0)
0.0
Hugs (Version: September 2006) has similar issues:
Hugs> compare (0/0) (0/0)
EQ
Hugs> compare (0/0) 1
EQ
Hugs> (0/0) == (0/0)
False
Hugs> min (0/0) 1
nan
Hugs> min 1 (0/0)
1.0
Hugs> max (0/0) 1
1.0
Discuss?
--
Barak A. Pearlmutter

On 16:34 Thu 22 Apr , Barak A. Pearlmutter wrote:
Comparison of exceptional IEEE floating point numbers, like Nan, seems to have some bugs in ghci (version 6.12.1).
These are correct, according to the IEEE floating point standards:
Prelude> 0 < (0/0) False ... But these are inconsistent with the above, and arguably incorrect: ... Prelude> compare 0 (0/0) GT ... I'd suggest that compare involving a NaN should yield
error "violation of the law of the excluded middle"
The problem stems from the fact that Float and Double are instances of a class for totally ordered data types (namely Ord), which they are not. While it might be worthwhile to make compare error in this case, the consequences of this instance are much, much worse. For example, max is not commutative (as you have observed). Data.Map.insert with Double keys can cause elements to disappear from the map (at least as far as Data.Map.lookup is concerned). Using "sort" on a list of doubles exposes the underlying sorting algorithm used. -- Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)

On Thu, Apr 22, 2010 at 11:34 AM, Barak A. Pearlmutter
Comparison of exceptional IEEE floating point numbers, like Nan, seems to have some bugs in ghci (version 6.12.1).
Arguably, the "bug" in question is the mere existence of Eq and Ord instances for IEEE floats. They don't, can't, and never will work correctly. A similar topic was discussed here not too long ago; IEEE floating point so-called "numbers" lack reflexive equality and associativity of addition and multiplication, among other properties one might take for granted in anything calling itself a number. If memory serves me, someone provided this informative link in the previous thread: http://docs.sun.com/source/806-3568/ncg_goldberg.html That said, given that Haskell seems to be following the well-established tradition of willfully disregarding the inconvenient aspects of floats as far as the type system is concerned, I would say that compare returning GT is particularly unintuitive. If something must stand in for a result of "arguments are non-comparable", EQ is marginally more appealing, as it is expected to be reflexive, as "non-comparable" is. An invalid comparison evaluating to _|_ is arguably more correct, but I personally find the idea of introducing more bottoms rather distasteful. On the other hand, crashing the program is usually better than incorrect results, so in this case it's probably justified. The only correct solution would be to strip floating point types of their instances for Ord, Eq, and--therefore, by extension--Num. For some reason, no one else seems to like that idea. I can't imagine why... - C.

On 13:30 Thu 22 Apr , Casey McCann wrote:
On Thu, Apr 22, 2010 at 11:34 AM, Barak A. Pearlmutter
wrote: Comparison of exceptional IEEE floating point numbers, like Nan, seems to have some bugs in ghci (version 6.12.1).
Arguably, the "bug" in question is the mere existence of Eq and Ord instances for IEEE floats. They don't, can't, and never will work correctly. A similar topic was discussed here not too long ago; IEEE floating point so-called "numbers" lack reflexive equality and associativity of addition and multiplication, among other properties one might take for granted in anything calling itself a number.
Lack of reflexivity in the Eq instance is, in my opinion, an extremely minor detail. I can't think of any library functions off-hand that both (a) Might reasonably be used in the context of floating point computation. (b) In the presence of NaNs, depend on reflexivity of (==) for correct behaviour. Now, lack of totality of the Ord instance is actually a severe problem, because I can immediately think of a function that is both useful and depends on this: sort. If we define "list is sorted" as "every element except the last is less than or equal to its successor", sort does not necessarily produce a sorted list! In fact, as I posted elsewhere, the result of sort in this case depends on the particular algorithm used. For all intents and purposes, a class for partial orders would be totally fine for floating point. Sure, it's not reflexive in the presence of NaNs. Sure, it's not antisymmetric in the presence of negative zeros. On the other hand, it does satisfy a restricted form of reflexivity and antisymmetry: * x == y implies x <= y * x <= y and y <= x implies x == y -- Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)

... An invalid comparison evaluating to _|_ is arguably more correct, but I personally find the idea of introducing more bottoms rather distasteful.
Too late! NaN is pretty much the _|_ of IEEE Floating Point. That was certainly the intent of the IEEE standard, and is why NaN is so contagious. But they wanted to relax the usual strictness of their languages (FORTRAN, C) when this particular _|_ is around. So NaN is contagious through strict arithmetic (+, *, etc) like _|_. But it has strange behaviour with respect to comparison. In the context of Haskell, which does not have the issue of needing to relax strictness just for NaN, I think the "right thing" would be to have compare give _|_, and maybe also <, >, ==. After all, NaN is outside the carefully defined total ordering of all other IEEE floating point values including +/- Infinity. (By the stringent criteria some people are giving for allowing something to be Eq and Ord, Char would also be stripped of them, since after all Char includes _|_. Sort of.) --Barak.

On Fri, Apr 23, 2010 at 3:21 AM, Barak A. Pearlmutter
... An invalid comparison evaluating to _|_ is arguably more correct, but I personally find the idea of introducing more bottoms rather distasteful.
Too late! NaN is pretty much the _|_ of IEEE Floating Point.
Yes, of course. But I don't have to like it... What annoys me is that, conceptually, the silently-propagating NaNs more strongly resemble Nothing, with the arithmetic functions lifted into Maybe, Applicative-style. Likewise, comparisons could sensibly be interpreted as returning Maybe Bool or Maybe Ordering. But there's no good way to work that into Haskell without making floats incredibly awkward to use.
In the context of Haskell, which does not have the issue of needing to relax strictness just for NaN, I think the "right thing" would be to have compare give _|_, and maybe also <, >, ==. After all, NaN is outside the carefully defined total ordering of all other IEEE floating point values including +/- Infinity.
The reason this makes me unhappy is that evaluating bottoms is a terrible way to deal with error conditions in pure code. It also makes using floating point values in generic code written for Ord dangerous, because the generic code won't (and can't) do anything to check whether calling compare will produce _|_ even if both arguments are already known to be fully evaluated.
(By the stringent criteria some people are giving for allowing something to be Eq and Ord, Char would also be stripped of them, since after all Char includes _|_. Sort of.)
The difference, of course, is that getting _|_ as a result of using _|_ is tolerable; getting _|_ as a result of using only non-_|_ values makes me sad. To my mind, the fewer ways there are to accidentally introduce _|_, the better. - C.

Casey McCann wrote:
The only correct solution would be to strip floating point types of their instances for Ord, Eq, and--therefore, by extension--Num. For some reason, no one else seems to like that idea. I can't imagine why...
I'm not terribly opposed to it. But then, I've also defined classes for partial orderings[1] and for types containing transfinite values[2] in order to try to render floats usable. Also, don't forget some of the other bugs[3] in Hugs. [1] http://hackage.haskell.org/packages/archive/logfloat/0.12.1/doc/html/Data-Nu... [2] http://hackage.haskell.org/packages/archive/logfloat/0.12.1/doc/html/Data-Nu... [3] http://hackage.haskell.org/packages/archive/logfloat/0.12.1/doc/html/Hugs-Re... -- Live well, ~wren

Please think of the poor guys trying to write high-performance code in Haskell!
Like me? (Well, not in Haskell per-se, but in a pure functional context.) In all seriousness, I think it is reasonable when "isNaN x" for x < C x == C x > C C < x C == x C > x to all be False, for all floats C, even C=x, as a sort of efficient weak Bool bottom. This is what the FP hardware does --- so it is very efficient. But if you force the system to choose one of the three, which is what compare x C is doing, I think the result should be _|_. Because there is no way to choose, no reasonable Ordering to return. It is possible to write generic "Ord n =>" code under these conditions, if you're careful to case out <,==,> when you don't want a NaN to kill the computation, and when necessary handle the case that all three come out false. That's what good numeric programmers actually do. But "compare" giving a wrong Ordering is an invitation to get it wrong. --Barak.

On 24/04/2010, at 07:15, Barak A. Pearlmutter wrote:
In all seriousness, I think it is reasonable when "isNaN x" for x < C x == C x > C C < x C == x C > x to all be False, for all floats C, even C=x, as a sort of efficient weak Bool bottom. This is what the FP hardware does --- so it is very efficient.
But if you force the system to choose one of the three, which is what compare x C is doing, I think the result should be _|_. Because there is no way to choose, no reasonable Ordering to return.
It is possible to write generic "Ord n =>" code under these conditions, if you're careful to case out <,==,> when you don't want a NaN to kill the computation, and when necessary handle the case that all three come out false. That's what good numeric programmers actually do. But "compare" giving a wrong Ordering is an invitation to get it wrong.
And yet a lot of generic code is written in terms of compare. Even deriving(Ord) only produces compare and relies on standard definitions for other methods. Don't get me wrong, I don't think the current situation is ideal (although it doesn't seem all that bad to me). But this change would have far-reaching implications for performance which ought to be evaluated before it can be seriously considered, in my opinion. Roman

And yet a lot of generic code is written in terms of compare.
That's can be an advantage, because often that code *should* blow up when it gets a NaN. E.g., sorting a list of Floats which includes a NaN.
Even deriving(Ord) only produces compare and relies on standard definitions for other methods.
I don't think that's actually a problem. Surely the IEEE Floating Point types would give their own definitions of not just compare but also <, <=, etc, overriding the problematic deriving(Ord) definitions of comparison in terms of compare and vice-versa.
Don't get me wrong, I don't think the current situation is ideal (although it doesn't seem all that bad to me). But this change would have far-reaching implications for performance which ought to be evaluated before it can be seriously considered, in my opinion.
Completely agree. The underlying issue is when a NaN should be treated like a Nothing, and when it should be treated like _|_. It seems clear that in some places the Nothing interpretation is preferred (say, arithmetic), and in other places _|_ (say, commanding the aperture of a therapeutic radiation device). It is a subtle issue, with effects on coding style, allowable code transformations both manual and automatic, correctness, and efficiency. --Barak.

On 24/04/2010, at 19:56, Barak A. Pearlmutter wrote:
And yet a lot of generic code is written in terms of compare.
That's can be an advantage, because often that code *should* blow up when it gets a NaN. E.g., sorting a list of Floats which includes a NaN.
However, often you will know that the list doesn't contain NaNs and will still have to pay a performance penalty. It's a question of what the right default is - safety or performance. In the case of floating point numbers, I'm leaning towards performance. That said, I would be very much in favour of providing a SafeFloat or whatever type with much safer semantics than IEEE floats and trying to get people to use that type by default unless they really need the performance.
Even deriving(Ord) only produces compare and relies on standard definitions for other methods.
I don't think that's actually a problem. Surely the IEEE Floating Point types would give their own definitions of not just compare but also <, <=, etc, overriding the problematic deriving(Ord) definitions of comparison in terms of compare and vice-versa.
I was thinking of this: data T = T Double deriving ( Eq, Ord ) Unless I'm mistaken, at the moment GHC basically produces instance Ord T where compare (T x) (T y) = compare x y t < u = compare t u == LT ... That is, all comparisons on T would be paying the "NaN performance tax". Roman

It's a question of what the right default is - safety or performance. In the case of floating point numbers, I'm leaning towards performance.
I quite agree. Currently the standard prelude has default definition: ... compare x y | x == y = EQ | x <= y = LT | otherwise = GT I'd suggest compare x y | x == y = EQ | x <= y = LT | x >= y = GT | otherwise = error "violation of the law of the excluded middle" or even the most symmetric compare x y | x < y = LT | x == y = EQ | x > y = GT | otherwise = error "no consistent ordering" It is not clear to me that this would cause a measurable performance hit in the case of floating point numbers. We're talking about at most two extra instructions: a compare and a conditional branch. The operands are already in registers, and scheduling considerations make it quite likely that the extra instructions could be put into otherwise unoccupied slots. For datatypes like Int or Integer or Char where the compiler should know that the law of the excluded middle holds, there should be zero overhead.
I was thinking of this:
data T = T Double deriving ( Eq, Ord )
... GHC basically produces
instance Ord T where compare (T x) (T y) = compare x y t < u = compare t u == LT
That is indeed what it does. Which is a plain old bug, since it leads to inconsistent behaviour between wrapped vs unwrapped values. *Main> T (0/0) == T (0/0) False *Main> T (0/0) < T (0/0) False *Main> T (0/0) > T (0/0) True *Main> (0/0) > (0/0) False GHC should instead basically produce ... (T x) < (T y) = x < y etc. --Barak.

On 24/04/2010, at 22:06, Barak A. Pearlmutter wrote:
Currently the standard prelude has default definition:
... compare x y | x == y = EQ | x <= y = LT | otherwise = GT
I'd suggest
[...]
compare x y | x < y = LT | x == y = EQ | x > y = GT | otherwise = error "no consistent ordering"
It is not clear to me that this would cause a measurable performance hit in the case of floating point numbers. We're talking about at most two extra instructions: a compare and a conditional branch. The
The problem are not so much the additional instructions. Rather, it's the fact that compare for Float and Double can fail at all which inhibits some optimisations. For instance, GHC is free to eliminate the comparison in (x `compare` y) `seq` a but wouldn't be with your change. It doesn't actually do that at the moment, which looks like an optimiser deficiency to me. But in any case, the property "can fail" has a significant effect on optimisations sometimes.
I was thinking of this:
data T = T Double deriving ( Eq, Ord )
... GHC basically produces
instance Ord T where compare (T x) (T y) = compare x y t < u = compare t u == LT
That is indeed what it does. Which is a plain old bug, since it leads to inconsistent behaviour between wrapped vs unwrapped values.
*Main> T (0/0) == T (0/0) False *Main> T (0/0) < T (0/0) False *Main> T (0/0) > T (0/0) True *Main> (0/0) > (0/0) False
Urgh. You're right, I hadn't thought of this. Would you care to submit a bug report? Roman

The problem are not so much the additional instructions. Rather, it's the fact that compare for Float and Double can fail at all which inhibits some optimisations. For instance, GHC is free to eliminate the comparison in (x `compare` y) `seq` a but wouldn't be with your change. It doesn't actually do that at the moment, which looks like an optimiser deficiency to me. But in any case, the property "can fail" has a significant effect on optimisations sometimes.
Yeah, the IEEE FP people knew what they were doing from a performance perspective. This kind of problem (eg, being able to remove a dead x+y without proving all kinds of conditions on x and y) is exactly whey they mandated a NaN value upon arithmetic exception rather than making the computation fail with a synchronous exception. Or at least, a mode, almost always used by default, with this behaviour. What you're describing is a similar performance problem, which argues for a similar solution: data Ordering = LT, EQ, GT, OoO where OoO means Out of Order. But just because you could doesn't mean you'd have to do this: compare x y = case map (\o->x`o`y) [(<),(<=),(==),(>=),(>),(/=)] of [True,True,False,False,False,True] -> LT [False,True,True,True,False,False] -> EQ [False,False,False,True,True,True] -> GT otherwise -> OoO --Barak.

It seems to me that there's a choice here between (A) Full conformance to the letter of IEEE arithmetic AND full conformance to the letter of Haskell total ordering with consequent inconvenience: don't make floats Ord create new IEEE comparison operations for floats (B) Full conformance to the letter of IEEE arithmetic and letting Haskell total ordering fend for itself with consequent incoherence: the present situation (C) Full conformance to the letter of Haskell total ordering and letting IEEE comparison rules blow away in the wind: x == y if and only if x may be substituted for y in any expression with no change in behaviour, making -0.0 < 0.0 necessary I think, and extending ordering to order NaNs I haven't seen anyone advocate this, although it seems like an obvious thing to think about. (D) Revising the Haskell class hierarchy to have a new ConfusingOrd class with weaker laws than Ord, and making the floating point numbers instances of that. This would NOT extend Eq, so == (which identifies +0.0 and -0.0, though they behave differently) would not be available for floats. class ConfusingOrd a where (===) :: a -> a -> Bool (/==) :: a -> a -> Bool (<) :: a -> a -> Bool ... class (Eq a, ConfusingOrd a) => Ord a where x === y = x == y x /== y = x /= y ... compare :: a -> a -> Ord To my feeble mind, this looks like possibly being the least troublesome of the alternatives. Yes, we'd stop being able to sort collections of floats using compare, but there's a way around that. See (E). (E) Have two sets of floating point numbers: floats and ordered-floats, with explicit coercion from floats to ordered-floats that might fail and explicit coercion from ordered-floats to floats that always succeeds. To sort a list, we might do map fromOrderedFloat (sort [x | Just x <- map toOrderedFloat ys])

On Sun, Apr 25, 2010 at 9:08 PM, Richard O'Keefe
It seems to me that there's a choice here between (...)
Nice! That's a very comprehensive summary of the situation regarding issues of correctness. I do wonder, though, what (if any) are the performance implications? Editorializing a bit, I would actually go so far as to say that, in the general case, using floating point values at all is a mistake. Programmers failing to use them properly has been a small but consistent source of bugs, even in low-level languages where one would expect familiarity with their behavior to be the norm. The situation is even worse in languages that are interpreted, VM-based, or otherwise further removed from the hardware level, where I've seen people who thought that IEEE specified behavior was a bug in the language runtime. To that end, I'd make a simultaneously conservative and radical suggestion: Regard floating point types as, first and foremost, a performance optimization, and strongly discourage their use as general-purpose fractional numbers. Aside from issues of backwards compatibility and such, I'd even advocate removing floating point types from the Prelude and instead require an explicit import from a separate module in the standard libraries. Use of floating point values would, ideally, be limited to calculation-heavy code which spends a non-trivial amount of its time doing fractional arithmetic, with an assumption that anyone writing code like that ought to understand both IEEE floats and Haskell's handling of them well enough to do it correctly. Given that distinction, I'd say that the order of priorities for floats should be 1) anything that supports writing high-performance code 2) accuracy to IEEE standards as the expected behavior 3) minimize the ugliness from a Haskell perspective as much as possible without harming the first two. What that works out to, I'm not sure, but I'd tolerate creating _|_s or breaking Ord's semantics if that's what it takes. Alas, I expect that's far too disruptive of existing code to be a viable approach. - C.

On 24/04/2010, at 22:42, Roman Leshchinskiy wrote:
On 24/04/2010, at 22:06, Barak A. Pearlmutter wrote:
I was thinking of this:
data T = T Double deriving ( Eq, Ord )
... GHC basically produces
instance Ord T where compare (T x) (T y) = compare x y t < u = compare t u == LT
That is indeed what it does. Which is a plain old bug, since it leads to inconsistent behaviour between wrapped vs unwrapped values.
*Main> T (0/0) == T (0/0) False *Main> T (0/0) < T (0/0) False *Main> T (0/0) > T (0/0) True *Main> (0/0) > (0/0) False
Urgh. You're right, I hadn't thought of this. Would you care to submit a bug report?
I submitted one but on further reflection, this is not so simple. Let's look at pairs as an example. At the moment, (>) is implemented basically like this: (a,b) > (c,d) = case compare a c of LT -> False EQ -> compare b d GT -> True Of course, this means that (0/0,'a') > (0/0,'a'). So we could change the implementation: (a,b) > (c,d) = a > c || (a == c && b > d) But now we compare a to c twice which is very bad for, say, ([Int],Int). Clearly, we want to use the first definition but it leads to inconsistent results for Doubles. I don't see how to solve this while keeping IEEE semantics of silent NaNs. Roman

On Sat, Apr 24, 2010 at 5:56 AM, Barak A. Pearlmutter
Even deriving(Ord) only produces compare and relies on standard definitions for other methods.
I don't think that's actually a problem. Surely the IEEE Floating Point types would give their own definitions of not just compare but also <, <=, etc, overriding the problematic deriving(Ord) definitions of comparison in terms of compare and vice-versa.
There is the issue of deriving Ord for algebraic types that include Float.
data Foo = Foo Float deriving (Show, Eq, Ord)
*Main> Foo (0/0) > Foo (0/0)
True
*Main> 0/0 > 0/0
False
If compare (0/0) (0/0) = _|_, then Foo (0/0) == Foo (0/0) = _|_.
--
Dave Menendez
participants (7)
-
Barak A. Pearlmutter
-
Casey McCann
-
David Menendez
-
Nick Bowler
-
Richard O'Keefe
-
Roman Leshchinskiy
-
wren ng thornton