Add Ord Laws to next Haskell Report

Per GHC.Classes (haddock-viewable from Data.Ord) "The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:" I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.

On Wed, Feb 6, 2019 at 9:43 PM chessai .
Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report. 6.3.2 The Ord Class class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a compare x y | x == y = EQ | x <= y = LT | otherwise = GT x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT -- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects. The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.

Does the wording of the report specify "totally ordered" as a law? I think
it would be good to make that explicit, laying out the axioms for what a
total order is—similar to the current documentation in Data.Ord but
explicitly as the laws for the class.
The relationship between Eq and Ord should be explicitly specified too, if
it isn't.
On Wed, Feb 6, 2019, 12:53 Herbert Valerio Riedel On Wed, Feb 6, 2019 at 9:43 PM chessai . Per GHC.Classes (haddock-viewable from Data.Ord) "The Haskell Report defines no laws for Ord. However, <= is
customarily expected to implement a non-strict partial order and have
the following properties:" I propose that in the next report that the expected typeclass laws for
Ord be added. They're generally agreed upon/understood. Can you spell out the concrete change to the report wording you're
suggesting? For reference, the current wording used in the 2010 Haskell
Report is quoted below. While at it, you might also want to take into
account the `Eq` class definition in the report. 6.3.2 The Ord Class class (Eq a) => Ord a where
compare :: a -> a -> Ordering
(<), (<=), (>=), (>) :: a -> a -> Bool
max, min :: a -> a -> a compare x y | x == y = EQ
| x <= y = LT
| otherwise = GT x <= y = compare x y /= GT
x < y = compare x y == LT
x >= y = compare x y /= LT
x > y = compare x y == GT -- Note that (min x y, max x y) = (x,y) or (y,x)
max x y | x <= y = y
| otherwise = x
min x y | x <= y = x
| otherwise = y The Ord class is used for totally ordered datatypes. All basic datatypes
except for functions, IO, and IOError, are instances of this class.
Instances of Ord can be derived for any user-defined datatype whose
constituent types are in Ord. The declared order of the constructors in
the data declaration determines the ordering in derived Ord instances.
The Ordering datatype allows a single comparison to determine the precise
ordering of two objects. The default declarations allow a user to create an Ord instance either
with a type-specific compare function or with type-specific == and <=
functions. _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Sure. There are no explicit mention of the laws of Ord. I think they
should be explicitly stated in the report, perhaps like so:
---------- start proposed change
class (Eq a) => Ord a where
compare :: a -> a -> Ordering
(<), (<=), (>), (>=) :: a -> a -> Bool
max, min :: a -> a -> a
compare x y = if x == y then EQ
else if x <= y then LT
else GT
x < y = case compare x y of { LT -> True; _ -> False }
x <= y = case compare x y of { GT -> False; _ -> True }
x > y = case compare x y of { GT -> True; _ -> False }
x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x
min x y = if x <= y then x else y
{-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of
'Ord' can be derived for any user-defined datatype whose constituent
types are in 'Ord'. The declared order of the constructors in the data
declaration determines the ordering in the derived 'Ord' instances.
The 'Ordering' datatype allows a single comparison to determine the
precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and
is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b)
Transitivity (a <= b && b <= c = a <= c)
Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True).
---------- end proposed change
I don't particularly like the bit in the current documentation about
(<=) implementing a non-strict partial ordering, because if (<=)
constitutes a minimal definition of Ord and is required only to be a
partial ordering on the type parameterised by Ord, then why is Ord
required to be a total ordering? That seems sort of confusing. It
seems to me that the current documentation leans more toward 'Ord'
implementing a partial order than a total order. I can't speak for
others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so
specifying their relationship (Reflexivity is implied by Totality) and
also writing out what Totality means in the context of Ord makes sense
to me.
For Eq, the report currently states:
----------begin report quote
class Eq a where
(==), (/=) :: a -> a -> Bool
x /= y = not (x == y)
x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All
basic datatypes except for functions and IO are instances of this
class. Instances of Eq can be derived for any user-defined datatype
whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==,
each being defined in terms of the other. If an instance declaration
for Eq defines neither == nor /=, then both will loop. If one is
defined, the default method for the other will make use of the one
that is defined. If both are defined, neither default method is used.
----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where
(==), (/=) :: a -> a -> Bool
x /= y = not (x == y)
x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/=').
All the basic datatypes exported by the "Prelude" are instances of 'Eq',
and 'Eq' may be derived for any datatype whose constituents are also
instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal
are considered indistinguishable. A minimal instance of 'Eq'
implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True)
Symmetry (x == y = y == x)
Transitivity (x == y && y == z = x == z)
Substitutivity (x == y = f x == f y)
Negation (x /= y = not (x = y)
---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote: Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.

We cant add laws at the moment unless we change how the Ord instances for
Float and Double are defined. (which i think SHOULd happen, but needs some
care and has lots of implications)
there are several possible semantics we can choose that act as we expect
on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008,
section 5.10, which defines negative nans below -infity, positive nans
above +infty
(this has the nice property that you could check for not nan by -infty
<= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by
default, so the only "fully evaluated" floating point values are in the
interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and
pave the way towards doing something like one of the above), though theres
still much to do
also: the current definitions of min/max via compare aren't commutative if
either argument is nan (they become right biased or left biased, i forget
which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy
of ieee floating point 2008 (easy to google up a copy if that link doesnt
work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so:
---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote: Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're
suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes
except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either
with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

We can add laws while recognizing that some existing instances are not
lawful.
On Wed, Feb 6, 2019, 9:43 PM Carter Schonwald We cant add laws at the moment unless we change how the Ord instances for
Float and Double are defined. (which i think SHOULd happen, but needs some
care and has lots of implications) there are several possible semantics we can choose that act as we expect
on +/- infity and finite floats, but differ in the handling of nans option 1) use the total order defined in floating point standard 2008,
section 5.10, which defines negative nans below -infity, positive nans
above +infty
(this has the nice property that you could check for not nan by -infty
<= x && x <= infty) option 2) shift haskell/ GHC to having signalling NAN semantics by
default, so the only "fully evaluated" floating point values are in the
interval from negative to positive infinity , option 3) some mixture of the above I am slowly doing some patches to improve floating point bits in ghc (and
pave the way towards doing something like one of the above), though theres
still much to do also: the current definitions of min/max via compare aren't commutative if
either argument is nan (they become right biased or left biased, i forget
which) http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a
copy of ieee floating point 2008 (easy to google up a copy if that link
doesnt work) On Wed, Feb 6, 2019 at 4:31 PM chessai . Sure. There are no explicit mention of the laws of Ord. I think they
should be explicitly stated in the report, perhaps like so: ---------- start proposed change
class (Eq a) => Ord a where
compare :: a -> a -> Ordering
(<), (<=), (>), (>=) :: a -> a -> Bool
max, min :: a -> a -> a compare x y = if x == y then EQ
else if x <= y then LT
else GT x < y = case compare x y of { LT -> True; _ -> False }
x <= y = case compare x y of { GT -> False; _ -> True }
x > y = case compare x y of { GT -> True; _ -> False }
x >= y = case compare x y of { LT -> False; _ -> True } max x y = if x <= y then y else x
min x y = if x <= y then x else y
{-# MINIMAL compare | (<=) #-} The `Ord` class is used for totally ordered datatypes. Instances of
'Ord' can be derived for any user-defined datatype whose constituent
types are in 'Ord'. The declared order of the constructors in the data
declaration determines the ordering in the derived 'Ord' instances.
The 'Ordering' datatype allows a single comparison to determine the
precise ordering of two objects. A minimal instance of 'Ord' implements either 'compare' or '<=', and
is expected to adhere to the following laws: Antisymmetry (a <= b && b <= a = a == b)
Transitivity (a <= b && b <= c = a <= c)
Totality (a <= b || b <= a = True) An additional law, Reflexity, is implied by Totality. It states (x <= x =
True).
---------- end proposed change I don't particularly like the bit in the current documentation about
(<=) implementing a non-strict partial ordering, because if (<=)
constitutes a minimal definition of Ord and is required only to be a
partial ordering on the type parameterised by Ord, then why is Ord
required to be a total ordering? That seems sort of confusing. It
seems to me that the current documentation leans more toward 'Ord'
implementing a partial order than a total order. I can't speak for
others, but when I think of 'Ord' I usually think of a total ordering. Additionally, Reflexity is strictly weaker than Totality, so
specifying their relationship (Reflexivity is implied by Totality) and
also writing out what Totality means in the context of Ord makes sense
to me. For Eq, the report currently states: ----------begin report quote
class Eq a where
(==), (/=) :: a -> a -> Bool x /= y = not (x == y)
x == y = not (x /= y) The Eq class provides equality (==) and inequality (/=) methods. All
basic datatypes except for functions and IO are instances of this
class. Instances of Eq can be derived for any user-defined datatype
whose constituents are also instances of Eq. This declaration gives default method declarations for both /= and ==,
each being defined in terms of the other. If an instance declaration
for Eq defines neither == nor /=, then both will loop. If one is
defined, the default method for the other will make use of the one
that is defined. If both are defined, neither default method is used.
----------end report quote I think the following changes make sense: ---------- begin proposed changes class Eq a where
(==), (/=) :: a -> a -> Bool
x /= y = not (x == y)
x == y = not (x /= y) The 'Eq' class defines equality ('==') and inequality ('/=').
All the basic datatypes exported by the "Prelude" are instances of 'Eq',
and 'Eq' may be derived for any datatype whose constituents are also
instances of 'Eq'. '==' implements an equivalence relationship where two values comparing
equal
are considered indistinguishable. A minimal instance of 'Eq'
implements either '==' or '/=', and must adhere to the following laws: Reflexivity (x == x = True)
Symmetry (x == y = y == x)
Transitivity (x == y && y == z = x == z)
Substitutivity (x == y = f x == f y)
Negation (x /= y = not (x = y)
---------- end proposed changes On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
On Wed, Feb 6, 2019 at 9:43 PM chessai . Per GHC.Classes (haddock-viewable from Data.Ord) "The Haskell Report defines no laws for Ord. However, <= is
customarily expected to implement a non-strict partial order and have
the following properties:" I propose that in the next report that the expected typeclass laws for
Ord be added. They're generally agreed upon/understood. Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell
Report is quoted below. While at it, you might also want to take into
account the `Eq` class definition in the report. 6.3.2 The Ord Class class (Eq a) => Ord a where
compare :: a -> a -> Ordering
(<), (<=), (>=), (>) :: a -> a -> Bool
max, min :: a -> a -> a compare x y | x == y = EQ
| x <= y = LT
| otherwise = GT x <= y = compare x y /= GT
x < y = compare x y == LT
x >= y = compare x y /= LT
x > y = compare x y == GT -- Note that (min x y, max x y) = (x,y) or (y,x)
max x y | x <= y = y
| otherwise = x
min x y | x <= y = x
| otherwise = y The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this
class. Instances of Ord can be derived for any user-defined datatype whose
constituent types are in Ord. The declared order of the constructors in the
data declaration determines the ordering in derived Ord instances. The
Ordering datatype allows a single comparison to determine the precise
ordering of two objects. The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <=
functions. _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

true, i just actually WANT to fixup those corners of float, assuming impact
can be managed suitably
On Wed, Feb 6, 2019 at 10:30 PM David Feuer
We can add laws while recognizing that some existing instances are not lawful.
On Wed, Feb 6, 2019, 9:43 PM Carter Schonwald
We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so:
---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote:
Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

(and to be even clearer, its definitely something where any help on
determining impact and minimizing it would be a pure joy to have )
On Wed, Feb 6, 2019 at 10:42 PM Carter Schonwald
true, i just actually WANT to fixup those corners of float, assuming impact can be managed suitably
On Wed, Feb 6, 2019 at 10:30 PM David Feuer
wrote: We can add laws while recognizing that some existing instances are not lawful.
On Wed, Feb 6, 2019, 9:43 PM Carter Schonwald
We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so:
---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote:
Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws
for
Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I guess the OTHER important reason is: any code that assumes those putative
laws will break horribly on floating point data types in the presence of
NAN values for any code that assumes those laws (but only when NANs happen
)
On Wed, Feb 6, 2019 at 10:46 PM Carter Schonwald
(and to be even clearer, its definitely something where any help on determining impact and minimizing it would be a pure joy to have )
On Wed, Feb 6, 2019 at 10:42 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
true, i just actually WANT to fixup those corners of float, assuming impact can be managed suitably
On Wed, Feb 6, 2019 at 10:30 PM David Feuer
wrote: We can add laws while recognizing that some existing instances are not lawful.
On Wed, Feb 6, 2019, 9:43 PM Carter Schonwald < carter.schonwald@gmail.com wrote:
We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so:
---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote:
> > Per GHC.Classes (haddock-viewable from Data.Ord) > > "The Haskell Report defines no laws for Ord. However, <= is > customarily expected to implement a non-strict partial order and have > the following properties:" > > I propose that in the next report that the expected typeclass laws for > Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yeah, Float/Double are always a problem when it comes to Ord. I think
it might be best to just acknowledge their unlawfulness. It's
unfortunate that they have Ord instances at all, IMO, but at this
point there's no changing that.
On Thu, Feb 7, 2019 at 12:02 AM Carter Schonwald
I guess the OTHER important reason is: any code that assumes those putative laws will break horribly on floating point data types in the presence of NAN values for any code that assumes those laws (but only when NANs happen )
On Wed, Feb 6, 2019 at 10:46 PM Carter Schonwald
wrote: (and to be even clearer, its definitely something where any help on determining impact and minimizing it would be a pure joy to have )
On Wed, Feb 6, 2019 at 10:42 PM Carter Schonwald
wrote: true, i just actually WANT to fixup those corners of float, assuming impact can be managed suitably
On Wed, Feb 6, 2019 at 10:30 PM David Feuer
wrote: We can add laws while recognizing that some existing instances are not lawful.
On Wed, Feb 6, 2019, 9:43 PM Carter Schonwald
We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so:
---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: > > > > > > On Wed, Feb 6, 2019 at 9:43 PM chessai . wrote: >> >> Per GHC.Classes (haddock-viewable from Data.Ord) >> >> "The Haskell Report defines no laws for Ord. However, <= is >> customarily expected to implement a non-strict partial order and have >> the following properties:" >> >> I propose that in the next report that the expected typeclass laws for >> Ord be added. They're generally agreed upon/understood. > > > > Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report. > > > 6.3.2 The Ord Class > > class (Eq a) => Ord a where > compare :: a -> a -> Ordering > (<), (<=), (>=), (>) :: a -> a -> Bool > max, min :: a -> a -> a > > compare x y | x == y = EQ > | x <= y = LT > | otherwise = GT > > x <= y = compare x y /= GT > x < y = compare x y == LT > x >= y = compare x y /= LT > x > y = compare x y == GT > > -- Note that (min x y, max x y) = (x,y) or (y,x) > max x y | x <= y = y > | otherwise = x > min x y | x <= y = x > | otherwise = y > > The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects. > > The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions. > > > _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I was discussing this with Carter on IRC, so to chime in with my two cents: I think the default behaviour for Float/Double should use a trapping NaN. The current value NaN is as if every Double value has an implicit "fromJust" and finding out which part of larger computations/pipelines introduced the NaNs in your output is a pain. Trapping NaN would also eliminate the brokenness of Ord. If some people are really attached to value NaNs (why?!? What's wrong with you?) we could allow disabling trapping at compile or runtime so they get the old behaviour. Cheers, Merijn
On 7 Feb 2019, at 03:43, Carter Schonwald
wrote: We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so: ---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote: Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

While I'm sure it would be a lot of churn, couldn't we introduce a
`TotalOrd` class and guard it more carefully?
On Thu, Feb 7, 2019 at 10:45 AM Merijn Verstraaten
I was discussing this with Carter on IRC, so to chime in with my two cents:
I think the default behaviour for Float/Double should use a trapping NaN. The current value NaN is as if every Double value has an implicit "fromJust" and finding out which part of larger computations/pipelines introduced the NaNs in your output is a pain.
Trapping NaN would also eliminate the brokenness of Ord. If some people are really attached to value NaNs (why?!? What's wrong with you?) we could allow disabling trapping at compile or runtime so they get the old behaviour.
Cheers, Merijn
On 7 Feb 2019, at 03:43, Carter Schonwald
wrote: We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so: ---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote:
Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Given that compare :: ... -> Ordering and Ordering = LT | EQ | GT, then the current Ord class has to support *total* orders, as there is no way to indicate when two elements are incomparable. Imagine trying to define the obvious partial ordering on sets - i.e. subset-or-equal using the Ord class. What should be the result, for Instance Ord (Set Int) of compare (fromList [1]) (fromList [2]) or fromList [2] <= fromList [1] ? Cheers, Andrew
On 7 Feb 2019, at 16:21, Elliot Cameron
wrote: While I'm sure it would be a lot of churn, couldn't we introduce a `TotalOrd` class and guard it more carefully?
On Thu, Feb 7, 2019 at 10:45 AM Merijn Verstraaten
mailto:merijn@inconsistent.nl> wrote: I was discussing this with Carter on IRC, so to chime in with my two cents: I think the default behaviour for Float/Double should use a trapping NaN. The current value NaN is as if every Double value has an implicit "fromJust" and finding out which part of larger computations/pipelines introduced the NaNs in your output is a pain.
Trapping NaN would also eliminate the brokenness of Ord. If some people are really attached to value NaNs (why?!? What's wrong with you?) we could allow disabling trapping at compile or runtime so they get the old behaviour.
Cheers, Merijn
On 7 Feb 2019, at 03:43, Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
mailto:chessai1996@gmail.com> wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so: ---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
mailto:hvriedel@gmail.com> wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
mailto:chessai1996@gmail.com> wrote: Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws for Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero@TCD, Head of Foundations & Methods Research Group School of Computer Science and Statistics, Room G.39, O'Reilly Institute, Trinity College, University of Dublin http://www.scss.tcd.ie/Andrew.Butterfield/ --------------------------------------------------------------------

hey Andrew B, agreed, partial orders aren't covered by Ord, and we are discussing only Ord here. theres a lot of good approaches to partial ords, but thats outside of scope for now :) On Thu, Feb 7, 2019 at 4:37 PM Andrew Butterfield < Andrew.Butterfield@scss.tcd.ie> wrote:
Given that compare :: ... -> Ordering and Ordering = LT | EQ | GT, then the current Ord class has to support *total* orders, as there is no way to indicate when two elements are incomparable.
Imagine trying to define the obvious partial ordering on sets - i.e. subset-or-equal using the Ord class. What should be the result, for Instance Ord (Set Int) of
compare (fromList [1]) (fromList [2]) or fromList [2] <= fromList [1] ?
Cheers, Andrew
On 7 Feb 2019, at 16:21, Elliot Cameron
wrote: While I'm sure it would be a lot of churn, couldn't we introduce a `TotalOrd` class and guard it more carefully?
On Thu, Feb 7, 2019 at 10:45 AM Merijn Verstraaten
wrote: I was discussing this with Carter on IRC, so to chime in with my two cents:
I think the default behaviour for Float/Double should use a trapping NaN. The current value NaN is as if every Double value has an implicit "fromJust" and finding out which part of larger computations/pipelines introduced the NaNs in your output is a pain.
Trapping NaN would also eliminate the brokenness of Ord. If some people are really attached to value NaNs (why?!? What's wrong with you?) we could allow disabling trapping at compile or runtime so they get the old behaviour.
Cheers, Merijn
On 7 Feb 2019, at 03:43, Carter Schonwald
wrote: We cant add laws at the moment unless we change how the Ord instances for Float and Double are defined. (which i think SHOULd happen, but needs some care and has lots of implications)
there are several possible semantics we can choose that act as we expect on +/- infity and finite floats, but differ in the handling of nans
option 1) use the total order defined in floating point standard 2008, section 5.10, which defines negative nans below -infity, positive nans above +infty (this has the nice property that you could check for not nan by -infty <= x && x <= infty)
option 2) shift haskell/ GHC to having signalling NAN semantics by default, so the only "fully evaluated" floating point values are in the interval from negative to positive infinity ,
option 3) some mixture of the above
I am slowly doing some patches to improve floating point bits in ghc (and pave the way towards doing something like one of the above), though theres still much to do
also: the current definitions of min/max via compare aren't commutative if either argument is nan (they become right biased or left biased, i forget which)
http://www.dsc.ufcg.edu.br/~cnum/modulos/Modulo2/IEEE754_2008.pdf is a copy of ieee floating point 2008 (easy to google up a copy if that link doesnt work)
On Wed, Feb 6, 2019 at 4:31 PM chessai .
wrote: Sure. There are no explicit mention of the laws of Ord. I think they should be explicitly stated in the report, perhaps like so: ---------- start proposed change class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a
compare x y = if x == y then EQ else if x <= y then LT else GT
x < y = case compare x y of { LT -> True; _ -> False } x <= y = case compare x y of { GT -> False; _ -> True } x > y = case compare x y of { GT -> True; _ -> False } x >= y = case compare x y of { LT -> False; _ -> True }
max x y = if x <= y then y else x min x y = if x <= y then x else y {-# MINIMAL compare | (<=) #-}
The `Ord` class is used for totally ordered datatypes. Instances of 'Ord' can be derived for any user-defined datatype whose constituent types are in 'Ord'. The declared order of the constructors in the data declaration determines the ordering in the derived 'Ord' instances. The 'Ordering' datatype allows a single comparison to determine the precise ordering of two objects.
A minimal instance of 'Ord' implements either 'compare' or '<=', and is expected to adhere to the following laws:
Antisymmetry (a <= b && b <= a = a == b) Transitivity (a <= b && b <= c = a <= c) Totality (a <= b || b <= a = True)
An additional law, Reflexity, is implied by Totality. It states (x <= x = True). ---------- end proposed change
I don't particularly like the bit in the current documentation about (<=) implementing a non-strict partial ordering, because if (<=) constitutes a minimal definition of Ord and is required only to be a partial ordering on the type parameterised by Ord, then why is Ord required to be a total ordering? That seems sort of confusing. It seems to me that the current documentation leans more toward 'Ord' implementing a partial order than a total order. I can't speak for others, but when I think of 'Ord' I usually think of a total ordering.
Additionally, Reflexity is strictly weaker than Totality, so specifying their relationship (Reflexivity is implied by Totality) and also writing out what Totality means in the context of Ord makes sense to me.
For Eq, the report currently states:
----------begin report quote class Eq a where (==), (/=) :: a -> a -> Bool
x /= y = not (x == y) x == y = not (x /= y)
The Eq class provides equality (==) and inequality (/=) methods. All basic datatypes except for functions and IO are instances of this class. Instances of Eq can be derived for any user-defined datatype whose constituents are also instances of Eq.
This declaration gives default method declarations for both /= and ==, each being defined in terms of the other. If an instance declaration for Eq defines neither == nor /=, then both will loop. If one is defined, the default method for the other will make use of the one that is defined. If both are defined, neither default method is used. ----------end report quote
I think the following changes make sense:
---------- begin proposed changes
class Eq a where (==), (/=) :: a -> a -> Bool x /= y = not (x == y) x == y = not (x /= y)
The 'Eq' class defines equality ('==') and inequality ('/='). All the basic datatypes exported by the "Prelude" are instances of 'Eq', and 'Eq' may be derived for any datatype whose constituents are also instances of 'Eq'.
'==' implements an equivalence relationship where two values comparing equal are considered indistinguishable. A minimal instance of 'Eq' implements either '==' or '/=', and must adhere to the following laws:
Reflexivity (x == x = True) Symmetry (x == y = y == x) Transitivity (x == y && y == z = x == z) Substitutivity (x == y = f x == f y) Negation (x /= y = not (x = y) ---------- end proposed changes
On Wed, Feb 6, 2019 at 3:52 PM Herbert Valerio Riedel
wrote: On Wed, Feb 6, 2019 at 9:43 PM chessai .
wrote:
Per GHC.Classes (haddock-viewable from Data.Ord)
"The Haskell Report defines no laws for Ord. However, <= is customarily expected to implement a non-strict partial order and have the following properties:"
I propose that in the next report that the expected typeclass laws
for
Ord be added. They're generally agreed upon/understood.
Can you spell out the concrete change to the report wording you're suggesting? For reference, the current wording used in the 2010 Haskell Report is quoted below. While at it, you might also want to take into account the `Eq` class definition in the report.
6.3.2 The Ord Class
class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>=), (>) :: a -> a -> Bool max, min :: a -> a -> a
compare x y | x == y = EQ | x <= y = LT | otherwise = GT
x <= y = compare x y /= GT x < y = compare x y == LT x >= y = compare x y /= LT x > y = compare x y == GT
-- Note that (min x y, max x y) = (x,y) or (y,x) max x y | x <= y = y | otherwise = x min x y | x <= y = x | otherwise = y
The Ord class is used for totally ordered datatypes. All basic datatypes except for functions, IO, and IOError, are instances of this class. Instances of Ord can be derived for any user-defined datatype whose constituent types are in Ord. The declared order of the constructors in the data declaration determines the ordering in derived Ord instances. The Ordering datatype allows a single comparison to determine the precise ordering of two objects.
The default declarations allow a user to create an Ord instance either with a type-specific compare function or with type-specific == and <= functions.
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero@TCD, Head of Foundations & Methods Research Group School of Computer Science and Statistics, Room G.39, O'Reilly Institute, Trinity College, University of Dublin http://www.scss.tcd.ie/Andrew.Butterfield/ --------------------------------------------------------------------
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Thu, 7 Feb 2019, Andrew Butterfield wrote:
Imagine trying to define the obvious partial ordering on sets - i.e. subset-or-equal using the Ord class. What should be the result, for Instance Ord (Set Int) of
compare (fromList [1]) (fromList [2]) or fromList [2] <= fromList [1] ?
Partial ordering means to me that the comparison function is partial. I.e. fromList [2] <= fromList [1] would be "undefined".

On Fri, 8 Feb 2019, 12:20 am Henning Thielemann, < lemming@henning-thielemann.de> wrote:
On Thu, 7 Feb 2019, Andrew Butterfield wrote:
Imagine trying to define the obvious partial ordering on sets - i.e. subset-or-equal using the Ord class. What should be the result, for Instance Ord (Set Int) of
compare (fromList [1]) (fromList [2]) or fromList [2] <= fromList [1] ?
Partial ordering means to me that the comparison function is partial. I.e. fromList [2] <= fromList [1] would be "undefined".__________________
Oh heavens no! It's very useful to ask whether two elements are comparable, that's a nightmare with this approach.
_____________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On Fri, 8 Feb 2019, Oliver Charles wrote:
On Fri, 8 Feb 2019, 12:20 am Henning Thielemann,
wrote: On Thu, 7 Feb 2019, Andrew Butterfield wrote:
> Imagine trying to define the obvious partial ordering on sets - i.e. > subset-or-equal using the Ord class. What should be the result, for > Instance Ord (Set Int) of > > compare (fromList [1]) (fromList [2]) or fromList [2] <= fromList [1] ?
Partial ordering means to me that the comparison function is partial. I.e. fromList [2] <= fromList [1] would be "undefined".__________________
Oh heavens no! It's very useful to ask whether two elements are comparable, that's a nightmare with this approach.
With the signature of 'compare' we can hardly do it better. That's why it is certainly better to leave Ord for total orderings and define class PartialOrd a where maybeCompare :: a -> a -> Maybe Ordering

On Fri, 8 Feb 2019, 9:54 am Henning Thielemann, < lemming@henning-thielemann.de> wrote:
With the signature of 'compare' we can hardly do it better. That's why it is certainly better to leave Ord for total orderings and define
class PartialOrd a where maybeCompare :: a -> a -> Maybe Ordering
Yes, precisely. For a moment I thought you were suggesting we should use Ord for partial orders.

On Thu, 7 Feb 2019, Merijn Verstraaten wrote:
I think the default behaviour for Float/Double should use a trapping NaN. The current value NaN is as if every Double value has an implicit "fromJust"
I like to think of it like all operations are lifted to (Maybe Float).
Trapping NaN would also eliminate the brokenness of Ord. If some people are really attached to value NaNs (why?!? What's wrong with you?) we could allow disabling trapping at compile or runtime so they get the old behaviour.
What about calling into foreign code? If I call a BLAS routine and one element of the result vector is NaN, shall this be trapped? Or shall it be trapped once I access the NaN element?

Am Do., 7. Feb. 2019 um 17:22 Uhr schrieb Henning Thielemann < lemming@henning-thielemann.de>:
[...] What about calling into foreign code? If I call a BLAS routine and one element of the result vector is NaN, shall this be trapped? Or shall it be trapped once I access the NaN element?
IMHO this is the biggest show stopper for some exotic NaN handling, as correct as it may be mathematically or aesthetically: The floating point environment is a thread-local (i.e. basically global) entity on most platforms, and most programming language runtimes expect a "default" environment, i.e. no traps when NaNs are encountered. So if Haskell wants to do things differently, the FPE has to be set/reset around foreign calls and for around every Haskell callback. I am not sure if this is really worth the trouble and the performance loss. For some special applications it might be OK or even important, but my gut feeling is that trapping NaNs is the wrong default in our current world...

@sven and @henning :
i'm actually doing some preliminary work to add save and restore for FPU
state to the GHC RTS, at the green/haskell thread layer. after first
ripping out x87 code gen, which just needs some more docs written out
before its merged in. note that i'm speaking specifically of the MXCSR
register save and restore, not the more hefty operations you might be
thinking.
FPU mode state save and restore is done already on EVERY OS when switching
threads/processes, and in the agner fog latency tables the cost of
manipulating mxcsr registers is pretty small!
https://www.agner.org/optimize/instruction_tables.pdf
LDMXCSR (restore) and STMXCSR (save) have cpu latencies at like 5-20
cycles (more often 8-15), so having the current C ffi calls set the
default C FPU environment (as we currently have ordinarily) is super doable
to ensure no breakage of existing C bindings, plus have a new ccall variant
that inherits the host haskell thread FPU state. we're talking sub 10
nanosecond overhead on x86 and x86_64 platforms (and either way, on those
platforms soon ghc will only be using the sse2 or higher ).
point being: aside from like AMD piledriver micro architecture and some
stuff from VIA, the performance of the CPU instruction for the signalling
nans state setup and related rounding mode etc, should work perfectly well,
@Daniel Cartwright
Am Do., 7. Feb. 2019 um 17:22 Uhr schrieb Henning Thielemann < lemming@henning-thielemann.de>:
[...] What about calling into foreign code? If I call a BLAS routine and one element of the result vector is NaN, shall this be trapped? Or shall it be trapped once I access the NaN element?
IMHO this is the biggest show stopper for some exotic NaN handling, as correct as it may be mathematically or aesthetically: The floating point environment is a thread-local (i.e. basically global) entity on most platforms, and most programming language runtimes expect a "default" environment, i.e. no traps when NaNs are encountered. So if Haskell wants to do things differently, the FPE has to be set/reset around foreign calls and for around every Haskell callback. I am not sure if this is really worth the trouble and the performance loss. For some special applications it might be OK or even important, but my gut feeling is that trapping NaNs is the wrong default in our current world... _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

to further add weight, i'm still doing preliminary hackery on the
signalling approach, but the signalling for FP state stuff seems to be OS
thread local, so it can be treated as an exception perfectly well!
On Thu, Feb 7, 2019 at 4:27 PM Carter Schonwald
@sven and @henning : i'm actually doing some preliminary work to add save and restore for FPU state to the GHC RTS, at the green/haskell thread layer. after first ripping out x87 code gen, which just needs some more docs written out before its merged in. note that i'm speaking specifically of the MXCSR register save and restore, not the more hefty operations you might be thinking.
FPU mode state save and restore is done already on EVERY OS when switching threads/processes, and in the agner fog latency tables the cost of manipulating mxcsr registers is pretty small! https://www.agner.org/optimize/instruction_tables.pdf
LDMXCSR (restore) and STMXCSR (save) have cpu latencies at like 5-20 cycles (more often 8-15), so having the current C ffi calls set the default C FPU environment (as we currently have ordinarily) is super doable to ensure no breakage of existing C bindings, plus have a new ccall variant that inherits the host haskell thread FPU state. we're talking sub 10 nanosecond overhead on x86 and x86_64 platforms (and either way, on those platforms soon ghc will only be using the sse2 or higher ).
point being: aside from like AMD piledriver micro architecture and some stuff from VIA, the performance of the CPU instruction for the signalling nans state setup and related rounding mode etc, should work perfectly well,
@Daniel Cartwright
I do not support documenting false laws in any enshrined way, it will result in broken code. (Also i'm actually working to do some fixes, if you reread my remarks and merijn's, and i think we can have our cake and eat it, with the finest floats). Lets fix stuff and then document true laws! On Thu, Feb 7, 2019 at 12:05 PM Sven Panne
wrote: Am Do., 7. Feb. 2019 um 17:22 Uhr schrieb Henning Thielemann < lemming@henning-thielemann.de>:
[...] What about calling into foreign code? If I call a BLAS routine and one element of the result vector is NaN, shall this be trapped? Or shall it be trapped once I access the NaN element?
IMHO this is the biggest show stopper for some exotic NaN handling, as correct as it may be mathematically or aesthetically: The floating point environment is a thread-local (i.e. basically global) entity on most platforms, and most programming language runtimes expect a "default" environment, i.e. no traps when NaNs are encountered. So if Haskell wants to do things differently, the FPE has to be set/reset around foreign calls and for around every Haskell callback. I am not sure if this is really worth the trouble and the performance loss. For some special applications it might be OK or even important, but my gut feeling is that trapping NaNs is the wrong default in our current world... _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Even if Ord becomes lawful for floating point, there will still be massive
problems reasoning about it because the Num instances can't support the
ring laws, let alone the ordered ring laws. What should `compare NaN n` be?
If it's an exception, then the ordering is not total, you can't store NaN
in a Set, etc. If it's LT or GT, then you get a total ordering, but a
rather weird one. So yeah, you'd be able to store NaN in a Set and have an
NaN key in a Map, but then as soon as you start looking at where these are
coming from and where they're going, everything goes weird and you need
type-specific code anyway.
On Thu, Feb 7, 2019, 4:29 PM Carter Schonwald to further add weight, i'm still doing preliminary hackery on the
signalling approach, but the signalling for FP state stuff seems to be OS
thread local, so it can be treated as an exception perfectly well! On Thu, Feb 7, 2019 at 4:27 PM Carter Schonwald <
carter.schonwald@gmail.com> wrote: @sven and @henning :
i'm actually doing some preliminary work to add save and restore for FPU
state to the GHC RTS, at the green/haskell thread layer. after first
ripping out x87 code gen, which just needs some more docs written out
before its merged in. note that i'm speaking specifically of the MXCSR
register save and restore, not the more hefty operations you might be
thinking. FPU mode state save and restore is done already on EVERY OS when
switching threads/processes, and in the agner fog latency tables the cost
of manipulating mxcsr registers is pretty small!
https://www.agner.org/optimize/instruction_tables.pdf LDMXCSR (restore) and STMXCSR (save) have cpu latencies at like 5-20
cycles (more often 8-15), so having the current C ffi calls set the
default C FPU environment (as we currently have ordinarily) is super doable
to ensure no breakage of existing C bindings, plus have a new ccall variant
that inherits the host haskell thread FPU state. we're talking sub 10
nanosecond overhead on x86 and x86_64 platforms (and either way, on those
platforms soon ghc will only be using the sse2 or higher ). point being: aside from like AMD piledriver micro architecture and some
stuff from VIA, the performance of the CPU instruction for the signalling
nans state setup and related rounding mode etc, should work perfectly well, @Daniel Cartwright On Thu, Feb 7, 2019 at 12:05 PM Sven Panne Am Do., 7. Feb. 2019 um 17:22 Uhr schrieb Henning Thielemann <
lemming@henning-thielemann.de>: [...] What about calling into foreign code? If I call a BLAS routine
and one
element of the result vector is NaN, shall this be trapped? Or shall it
be
trapped once I access the NaN element? IMHO this is the biggest show stopper for some exotic NaN handling, as
correct as it may be mathematically or aesthetically: The floating point
environment is a thread-local (i.e. basically global) entity on most
platforms, and most programming language runtimes expect a "default"
environment, i.e. no traps when NaNs are encountered. So if Haskell wants
to do things differently, the FPE has to be set/reset around foreign calls
and for around every Haskell callback. I am not sure if this is really
worth the trouble and the performance loss. For some special applications
it might be OK or even important, but my gut feeling is that trapping NaNs
is the wrong default in our current world...
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

David,
We aren't talking about Ring laws here, so lets not pull that in yet please
:)
as Merijn also noted, one possible semantics is have signalling Nans, so
that any haskell calculation that yields a Nan instead triggers an
exception via cpu stuff. Or the next FP instruction that touches the nan
will trigger in the case of it coming from C land (I just reread all the
relevant sections of the intel architecture manual, its quite explicit on
this corner, and still be superbly IEEE float compliant, AND place nice
with code that DOES want nan via stateful stuff if need be)
on the matter of Nan, in a quiet nan universe, theres a whole universe of
Nans, and they're all different, and in fact the iEEE standard is quite
clear that a language could pick different nans for different errors (eg
have all the bits form a bit set of possible errors). Or one of several
other approaches.
point being, we can have nice things.
mind you, i'm still doing this hackery over time. But I genuinely see a
path thats thread safe, makes the MXCSR register state act local per
haskell thread, doesn't change the default semantics for C ffi calls, and
still allows those who want quiet NANs to do whatever they want if they
really really want to.
I do agree that any such changes can't break code in the wild that depends
on FPU state stuff, nor those who like Quiet Nans more than
exceptional/signalling ones. And thats a burden on me / any collaborators
for successful execution.
*punchline* Lawful Ord and NanFree Float for all, with no leaky breakages,
Every Num has Div By Zero error already, lets recognize all NAN
computations as being similarly exceptional by default. :)
On Thu, Feb 7, 2019 at 4:41 PM David Feuer
Even if Ord becomes lawful for floating point, there will still be massive problems reasoning about it because the Num instances can't support the ring laws, let alone the ordered ring laws. What should `compare NaN n` be? If it's an exception, then the ordering is not total, you can't store NaN in a Set, etc. If it's LT or GT, then you get a total ordering, but a rather weird one. So yeah, you'd be able to store NaN in a Set and have an NaN key in a Map, but then as soon as you start looking at where these are coming from and where they're going, everything goes weird and you need type-specific code anyway.
On Thu, Feb 7, 2019, 4:29 PM Carter Schonwald
to further add weight, i'm still doing preliminary hackery on the signalling approach, but the signalling for FP state stuff seems to be OS thread local, so it can be treated as an exception perfectly well!
On Thu, Feb 7, 2019 at 4:27 PM Carter Schonwald < carter.schonwald@gmail.com> wrote:
@sven and @henning : i'm actually doing some preliminary work to add save and restore for FPU state to the GHC RTS, at the green/haskell thread layer. after first ripping out x87 code gen, which just needs some more docs written out before its merged in. note that i'm speaking specifically of the MXCSR register save and restore, not the more hefty operations you might be thinking.
FPU mode state save and restore is done already on EVERY OS when switching threads/processes, and in the agner fog latency tables the cost of manipulating mxcsr registers is pretty small! https://www.agner.org/optimize/instruction_tables.pdf
LDMXCSR (restore) and STMXCSR (save) have cpu latencies at like 5-20 cycles (more often 8-15), so having the current C ffi calls set the default C FPU environment (as we currently have ordinarily) is super doable to ensure no breakage of existing C bindings, plus have a new ccall variant that inherits the host haskell thread FPU state. we're talking sub 10 nanosecond overhead on x86 and x86_64 platforms (and either way, on those platforms soon ghc will only be using the sse2 or higher ).
point being: aside from like AMD piledriver micro architecture and some stuff from VIA, the performance of the CPU instruction for the signalling nans state setup and related rounding mode etc, should work perfectly well,
@Daniel Cartwright
I do not support documenting false laws in any enshrined way, it will result in broken code. (Also i'm actually working to do some fixes, if you reread my remarks and merijn's, and i think we can have our cake and eat it, with the finest floats). Lets fix stuff and then document true laws! On Thu, Feb 7, 2019 at 12:05 PM Sven Panne
wrote: Am Do., 7. Feb. 2019 um 17:22 Uhr schrieb Henning Thielemann < lemming@henning-thielemann.de>:
[...] What about calling into foreign code? If I call a BLAS routine and one element of the result vector is NaN, shall this be trapped? Or shall it be trapped once I access the NaN element?
IMHO this is the biggest show stopper for some exotic NaN handling, as correct as it may be mathematically or aesthetically: The floating point environment is a thread-local (i.e. basically global) entity on most platforms, and most programming language runtimes expect a "default" environment, i.e. no traps when NaNs are encountered. So if Haskell wants to do things differently, the FPE has to be set/reset around foreign calls and for around every Haskell callback. I am not sure if this is really worth the trouble and the performance loss. For some special applications it might be OK or even important, but my gut feeling is that trapping NaNs is the wrong default in our current world... _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On 7 Feb 2019, at 22:41, David Feuer
wrote: Even if Ord becomes lawful for floating point, there will still be massive problems reasoning about it because the Num instances can't support the ring laws, let alone the ordered ring laws. What should `compare NaN n` be?
Our goal is to make "compare NaN n" impossible to happen. You can only (try) to compare with NaN if you can *get* a NaN value. But IEEE-754 pretty clearly does *NOT* require computations that evaluate to NaN to be represented as values. "Trap representations" (i.e., anything vaguely exception like) are an acceptable IEEE-754 compliant way of implementing NaN. All the major CPU platforms support trapping floating point exceptions, not many languages make use of this.
If it's an exception, then the ordering is not total, you can't store NaN in a Set, etc.
I think this argument is without merit. Yes, it would mean you can't store NaN in a Set anymore (because you wouldn't even be able to have a NaN value...). But that's like complaining Int is broken because I can't store "(5 `div` 0)" in a Set. So far everyone seems perfectly ok with the exception raised by division by zero, so why not NaN?
If it's LT or GT, then you get a total ordering, but a rather weird one. So yeah, you'd be able to store NaN in a Set and have an NaN key in a Map, but then as soon as you start looking at where these are coming from and where they're going, everything goes weird and you need type-specific code anyway.
If we accept value NaN's (as opposed to trapping NaNs) then we can't have Ord anyway, at least not without giving up on IEEE-754 compliance, as IEEE-754 demands "NaN" compares unequal with itself, which breaks any sort of ordering based function (even simple things like sort, as I painfully discovered in Python...) Cheers, Merijn

additionally (for posterity), merjin pointed out to me that we do want x/0
to not be an exception when abs(x)!= 0, because +/- infinity are perfectly
valid and useful mathematical objects
On Thu, Feb 7, 2019 at 5:31 PM Merijn Verstraaten
On 7 Feb 2019, at 22:41, David Feuer
wrote: Even if Ord becomes lawful for floating point, there will still be massive problems reasoning about it because the Num instances can't support the ring laws, let alone the ordered ring laws. What should `compare NaN n` be?
Our goal is to make "compare NaN n" impossible to happen. You can only (try) to compare with NaN if you can *get* a NaN value. But IEEE-754 pretty clearly does *NOT* require computations that evaluate to NaN to be represented as values.
"Trap representations" (i.e., anything vaguely exception like) are an acceptable IEEE-754 compliant way of implementing NaN. All the major CPU platforms support trapping floating point exceptions, not many languages make use of this.
If it's an exception, then the ordering is not total, you can't store NaN in a Set, etc.
I think this argument is without merit. Yes, it would mean you can't store NaN in a Set anymore (because you wouldn't even be able to have a NaN value...). But that's like complaining Int is broken because I can't store "(5 `div` 0)" in a Set. So far everyone seems perfectly ok with the exception raised by division by zero, so why not NaN?
If it's LT or GT, then you get a total ordering, but a rather weird one. So yeah, you'd be able to store NaN in a Set and have an NaN key in a Map, but then as soon as you start looking at where these are coming from and where they're going, everything goes weird and you need type-specific code anyway.
If we accept value NaN's (as opposed to trapping NaNs) then we can't have Ord anyway, at least not without giving up on IEEE-754 compliance, as IEEE-754 demands "NaN" compares unequal with itself, which breaks any sort of ordering based function (even simple things like sort, as I painfully discovered in Python...)
Cheers, Merijn

I think we've gotten a bit off-track here. Certainly we have
disagreements about what should be done regarding floating-point
values in GHC over the longer term, but that shouldn't hold up the
report.
I would prefer to see the total order laws added as Daniel suggested,
while documenting that Float and Double have non-lawful instances due
to NaNs. If the handling of doubles is later improved we can simply
delete that line of documentation.
On Fri, 8 Feb 2019 at 08:34, Carter Schonwald
additionally (for posterity), merjin pointed out to me that we do want x/0 to not be an exception when abs(x)!= 0, because +/- infinity are perfectly valid and useful mathematical objects
On Thu, Feb 7, 2019 at 5:31 PM Merijn Verstraaten
wrote: On 7 Feb 2019, at 22:41, David Feuer
wrote: Even if Ord becomes lawful for floating point, there will still be massive problems reasoning about it because the Num instances can't support the ring laws, let alone the ordered ring laws. What should `compare NaN n` be?
Our goal is to make "compare NaN n" impossible to happen. You can only (try) to compare with NaN if you can *get* a NaN value. But IEEE-754 pretty clearly does *NOT* require computations that evaluate to NaN to be represented as values.
"Trap representations" (i.e., anything vaguely exception like) are an acceptable IEEE-754 compliant way of implementing NaN. All the major CPU platforms support trapping floating point exceptions, not many languages make use of this.
If it's an exception, then the ordering is not total, you can't store NaN in a Set, etc.
I think this argument is without merit. Yes, it would mean you can't store NaN in a Set anymore (because you wouldn't even be able to have a NaN value...). But that's like complaining Int is broken because I can't store "(5 `div` 0)" in a Set. So far everyone seems perfectly ok with the exception raised by division by zero, so why not NaN?
If it's LT or GT, then you get a total ordering, but a rather weird one. So yeah, you'd be able to store NaN in a Set and have an NaN key in a Map, but then as soon as you start looking at where these are coming from and where they're going, everything goes weird and you need type-specific code anyway.
If we accept value NaN's (as opposed to trapping NaNs) then we can't have Ord anyway, at least not without giving up on IEEE-754 compliance, as IEEE-754 demands "NaN" compares unequal with itself, which breaks any sort of ordering based function (even simple things like sort, as I painfully discovered in Python...)
Cheers, Merijn
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

true enough
Another cool thing that was pointed out to me, is that for NanFree Floats,
the Projective reals (err, floats) with a single infinity become a new type
over float/double (subject to how reals and floats) release. (thanks to
Wren for that point )
On Thu, Feb 7, 2019 at 5:43 PM George Wilson
I think we've gotten a bit off-track here. Certainly we have disagreements about what should be done regarding floating-point values in GHC over the longer term, but that shouldn't hold up the report. I would prefer to see the total order laws added as Daniel suggested, while documenting that Float and Double have non-lawful instances due to NaNs. If the handling of doubles is later improved we can simply delete that line of documentation.
On Fri, 8 Feb 2019 at 08:34, Carter Schonwald
wrote: additionally (for posterity), merjin pointed out to me that we do want
x/0 to not be an exception when abs(x)!= 0, because +/- infinity are perfectly valid and useful mathematical objects
On Thu, Feb 7, 2019 at 5:31 PM Merijn Verstraaten <
On 7 Feb 2019, at 22:41, David Feuer
wrote: Even if Ord becomes lawful for floating point, there will still be
massive problems reasoning about it because the Num instances can't support
Our goal is to make "compare NaN n" impossible to happen. You can only
(try) to compare with NaN if you can *get* a NaN value. But IEEE-754 pretty clearly does *NOT* require computations that evaluate to NaN to be represented as values.
"Trap representations" (i.e., anything vaguely exception like) are an
acceptable IEEE-754 compliant way of implementing NaN. All the major CPU
merijn@inconsistent.nl> wrote: the ring laws, let alone the ordered ring laws. What should `compare NaN n` be? platforms support trapping floating point exceptions, not many languages make use of this.
If it's an exception, then the ordering is not total, you can't store
NaN in a Set, etc.
I think this argument is without merit. Yes, it would mean you can't
store NaN in a Set anymore (because you wouldn't even be able to have a NaN value...). But that's like complaining Int is broken because I can't store "(5 `div` 0)" in a Set. So far everyone seems perfectly ok with the exception raised by division by zero, so why not NaN?
If it's LT or GT, then you get a total ordering, but a rather weird
one. So yeah, you'd be able to store NaN in a Set and have an NaN key in a Map, but then as soon as you start looking at where these are coming from and where they're going, everything goes weird and you need type-specific code anyway.
If we accept value NaN's (as opposed to trapping NaNs) then we can't
have Ord anyway, at least not without giving up on IEEE-754 compliance, as IEEE-754 demands "NaN" compares unequal with itself, which breaks any sort of ordering based function (even simple things like sort, as I painfully discovered in Python...)
Cheers, Merijn
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yes, quite. This is only about clarifications to the report. All this other
stuff seems mostly tangential, and should probably be another thread.
On Thu, Feb 7, 2019, 5:44 PM George Wilson I think we've gotten a bit off-track here. Certainly we have
disagreements about what should be done regarding floating-point
values in GHC over the longer term, but that shouldn't hold up the
report.
I would prefer to see the total order laws added as Daniel suggested,
while documenting that Float and Double have non-lawful instances due
to NaNs. If the handling of doubles is later improved we can simply
delete that line of documentation. On Fri, 8 Feb 2019 at 08:34, Carter Schonwald
additionally (for posterity), merjin pointed out to me that we do want x/0 to not be an exception when abs(x)!= 0, because +/- infinity are
perfectly valid and useful mathematical objects On Thu, Feb 7, 2019 at 5:31 PM Merijn Verstraaten < On 7 Feb 2019, at 22:41, David Feuer Even if Ord becomes lawful for floating point, there will still be massive problems reasoning about it because the Num instances can't support Our goal is to make "compare NaN n" impossible to happen. You can only (try) to compare with NaN if you can *get* a NaN value. But IEEE-754 pretty
clearly does *NOT* require computations that evaluate to NaN to be
represented as values. "Trap representations" (i.e., anything vaguely exception like) are an acceptable IEEE-754 compliant way of implementing NaN. All the major CPU merijn@inconsistent.nl> wrote:
the ring laws, let alone the ordered ring laws. What should `compare NaN n`
be?
platforms support trapping floating point exceptions, not many languages
make use of this. If it's an exception, then the ordering is not total, you can't store NaN in a Set, etc. I think this argument is without merit. Yes, it would mean you can't store NaN in a Set anymore (because you wouldn't even be able to have a NaN
value...). But that's like complaining Int is broken because I can't store
"(5 `div` 0)" in a Set. So far everyone seems perfectly ok with the
exception raised by division by zero, so why not NaN? If it's LT or GT, then you get a total ordering, but a rather weird one. So yeah, you'd be able to store NaN in a Set and have an NaN key in a
Map, but then as soon as you start looking at where these are coming from
and where they're going, everything goes weird and you need type-specific
code anyway. If we accept value NaN's (as opposed to trapping NaNs) then we can't have Ord anyway, at least not without giving up on IEEE-754 compliance, as
IEEE-754 demands "NaN" compares unequal with itself, which breaks any sort
of ordering based function (even simple things like sort, as I painfully
discovered in Python...) Cheers,
Merijn _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>:
Our goal is to make "compare NaN n" impossible to happen. [...]
Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.

On 8 Feb 2019, at 10:57, Sven Panne
wrote: Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten
: Our goal is to make "compare NaN n" impossible to happen. [...] Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.
This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary. Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not. In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future. Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs. I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data. In other words, there are only two ways to get sane behaviour from Double with regards to ordering: 1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance. Cheers, Merijn

Thanks for eloquently summarizing , better than I would , what I thought I
had laid out.
Ieee floating point has fantastic hardware support . May as well be the
first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
On 8 Feb 2019, at 10:57, Sven Panne
wrote: Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>: Our goal is to make "compare NaN n" impossible to happen. [...]
Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.
This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I would *hate* to lose quiet NaNs. They can be very useful. But I’d be
fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap
as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
wrote: On 8 Feb 2019, at 10:57, Sven Panne
wrote: Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>: Our goal is to make "compare NaN n" impossible to happen. [...]
Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.
This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

No, no, no. Int and Word are *rings*, which let's us apply a ton of
mathematical reasoning to their arithmetic. Trapping overflow would throw
all that completely out the window. If you want to trap overflow, please
use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson I would *hate* to lose quiet NaNs. They can be very useful. But I’d be
fine having them as a separate type. And while we’re at it, why not make Int overflow and underflow cause a
trap as well? With a different type if you want to wrap. On Fri, Feb 8, 2019 at 08:34 Carter Schonwald Thanks for eloquently summarizing , better than I would , what I thought
I had laid out. Ieee floating point has fantastic hardware support . May as well be the
first real language to actually use it correctly. :) On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten On 8 Feb 2019, at 10:57, Sven Panne Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten <
merijn@inconsistent.nl>:
Our goal is to make "compare NaN n" impossible to happen. [...] Well, what is supposed to happen then when you *do* see a NaN, e.g.
one produced from a foreign call? You *will* see NaNs in Haskell if you
interact with other languages, most of them take a far less religious
approach to floating points calculations. This is not true. As Carter pointed out we can setup the CPU to trap
NaNs *even in foreign calls*. So, in theory we CAN rule this out safely.
Doing this we can simply convert the trap into an exception at the FFI
boundary. Now, there are cases were this is problematic, so as said before we will
probably need to allow people to optionally switch on 'value NaNs', because
the foreign code isn't exception safe or for other reasons, but this is
manageable. Via, for example having an annotation on foreign imports
whether you want to trap or not. In the scenario where someone switches to value NaNs, we are *still* not
worse off than we are now. The things you suggest already happen *now*, so
the only thing we're advocating is making it possible to have more sane
behaviour in the future. Any IEEE-754 compliant implementation of Double that doesn't use
trapping NaN can, by definition, never ever be a sane implementation of
Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't
apply to NaNs and there is *no* safe way to sort/order data containing NaNs. I've run into several nasty issues of trying to sort lists containing
NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs
that are affected, entire subsequences end up getting sorted wrong based on
the comparison with NaN and you end up with completely garbled and unsorted
data. In other words, there are only two ways to get sane behaviour from
Double with regards to ordering: 1. Trapping NaN represenation
2. Deviate from IEEE-754 semantics To me, option 2 is out of the question, it's the one consistent thing
across language we have when it comes to floating point. I understand that
*always* using trap representation isn't feasible, but allowing people to
optionally switch to value NaNs leaves us no worse off than we are *right
now*, and per above, there is literally no way to improve the situation wrt
value NaNs without sacrificing IEEE-754 compliance. Cheers,
Merijn
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I’m not sure if they currently have full ring structure , but I do agree
that trapping and non trapping int and word are useful.
Simple example where all the finite signed ints work wrong today :
There’s no proper additive inverse for minBound :: int
Likewise , what’s our current definition of negate on finite word types?
On Fri, Feb 8, 2019 at 2:12 PM David Feuer
No, no, no. Int and Word are *rings*, which let's us apply a ton of mathematical reasoning to their arithmetic. Trapping overflow would throw all that completely out the window. If you want to trap overflow, please use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
wrote: Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten < merijn@inconsistent.nl> wrote:
On 8 Feb 2019, at 10:57, Sven Panne
wrote: Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>: Our goal is to make "compare NaN n" impossible to happen. [...]
Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.
This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Most of the arguments for making them rings feel kind of pedantic, in any case. I can't think of a time I've ever used actual ring theory to reason about Ints/Words. On 2/8/19 1:27 PM, Carter Schonwald wrote:
I’m not sure if they currently have full ring structure , but I do agree that trapping and non trapping int and word are useful.
Simple example where all the finite signed ints work wrong today :
There’s no proper additive inverse for minBound :: int
Likewise , what’s our current definition of negate on finite word types?
On Fri, Feb 8, 2019 at 2:12 PM David Feuer
mailto:david.feuer@gmail.com> wrote: No, no, no. Int and Word are *rings*, which let's us apply a ton of mathematical reasoning to their arithmetic. Trapping overflow would throw all that completely out the window. If you want to trap overflow, please use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson
mailto:lennart@augustsson.net wrote: I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
mailto:merijn@inconsistent.nl> wrote: > On 8 Feb 2019, at 10:57, Sven Panne
mailto:svenpanne@gmail.com> wrote: > > Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten mailto:merijn@inconsistent.nl>: > Our goal is to make "compare NaN n" impossible to happen. [...] > > Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations. This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

minBound + minBound :: Int 0 negate minBound == (minBound :: Int) True 42 + negate 17 :: Word 25
Int and Word are currently rings. What proportion actually uses them as
such would be interesting to know but I guess it is very small. I wouldn't
dare to reason about Int and Word as rings as there is no guarantee on
which ring they are. Int64 and Word64 and so on; yes, those can be reasoned
about.
I'd be very happy to see a separate type for signalling integral types.
Personally, I'd make them the default choice.
On Fri, 8 Feb 2019 at 19:27, Carter Schonwald
I’m not sure if they currently have full ring structure , but I do agree that trapping and non trapping int and word are useful.
Simple example where all the finite signed ints work wrong today :
There’s no proper additive inverse for minBound :: int
Likewise , what’s our current definition of negate on finite word types?
On Fri, Feb 8, 2019 at 2:12 PM David Feuer
wrote: No, no, no. Int and Word are *rings*, which let's us apply a ton of mathematical reasoning to their arithmetic. Trapping overflow would throw all that completely out the window. If you want to trap overflow, please use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald < carter.schonwald@gmail.com> wrote:
Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten < merijn@inconsistent.nl> wrote:
On 8 Feb 2019, at 10:57, Sven Panne
wrote: Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>: Our goal is to make "compare NaN n" impossible to happen. [...]
Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.
This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

No. A ring can’t have 2x=0 for x not zero. Thus int can’t be
And by ring I mean an algebraic structure where you have a multiplicative
group that doesn’t generate zero from products of nonzero elements ...
Phrased differently: Int doesn’t have a multiplicative group structure on
the nonzero elements. That makes it a pretty nasty ring. Negate on minBound
should be an overflow exception so you can have actual sane semantics.
This is an old dead horse with lots of blood written about it.
https://ghc.haskell.org/trac/ghc/ticket/8695 has some related discussions
On Fri, Feb 8, 2019 at 2:53 PM Jens Blanck
minBound + minBound :: Int 0 negate minBound == (minBound :: Int) True 42 + negate 17 :: Word 25
Int and Word are currently rings. What proportion actually uses them as such would be interesting to know but I guess it is very small. I wouldn't dare to reason about Int and Word as rings as there is no guarantee on which ring they are. Int64 and Word64 and so on; yes, those can be reasoned about.
I'd be very happy to see a separate type for signalling integral types. Personally, I'd make them the default choice.
On Fri, 8 Feb 2019 at 19:27, Carter Schonwald
wrote: I’m not sure if they currently have full ring structure , but I do agree that trapping and non trapping int and word are useful.
Simple example where all the finite signed ints work wrong today :
There’s no proper additive inverse for minBound :: int
Likewise , what’s our current definition of negate on finite word types?
On Fri, Feb 8, 2019 at 2:12 PM David Feuer
wrote: No, no, no. Int and Word are *rings*, which let's us apply a ton of mathematical reasoning to their arithmetic. Trapping overflow would throw all that completely out the window. If you want to trap overflow, please use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald < carter.schonwald@gmail.com> wrote:
Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten < merijn@inconsistent.nl> wrote:
> On 8 Feb 2019, at 10:57, Sven Panne
wrote: > > Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>: > Our goal is to make "compare NaN n" impossible to happen. [...] > > Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations. This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I think the algebraic property we usually want for nice integer ish things
is intergral domain. Which is a stronger property than ring. Pardon the
confusion
On Fri, Feb 8, 2019 at 3:03 PM Carter Schonwald
No. A ring can’t have 2x=0 for x not zero. Thus int can’t be
And by ring I mean an algebraic structure where you have a multiplicative group that doesn’t generate zero from products of nonzero elements ...
Phrased differently: Int doesn’t have a multiplicative group structure on the nonzero elements. That makes it a pretty nasty ring. Negate on minBound should be an overflow exception so you can have actual sane semantics. This is an old dead horse with lots of blood written about it.
https://ghc.haskell.org/trac/ghc/ticket/8695 has some related discussions
On Fri, Feb 8, 2019 at 2:53 PM Jens Blanck
wrote: minBound + minBound :: Int 0 negate minBound == (minBound :: Int) True 42 + negate 17 :: Word 25
Int and Word are currently rings. What proportion actually uses them as such would be interesting to know but I guess it is very small. I wouldn't dare to reason about Int and Word as rings as there is no guarantee on which ring they are. Int64 and Word64 and so on; yes, those can be reasoned about.
I'd be very happy to see a separate type for signalling integral types. Personally, I'd make them the default choice.
On Fri, 8 Feb 2019 at 19:27, Carter Schonwald
wrote: I’m not sure if they currently have full ring structure , but I do agree that trapping and non trapping int and word are useful.
Simple example where all the finite signed ints work wrong today :
There’s no proper additive inverse for minBound :: int
Likewise , what’s our current definition of negate on finite word types?
On Fri, Feb 8, 2019 at 2:12 PM David Feuer
wrote: No, no, no. Int and Word are *rings*, which let's us apply a ton of mathematical reasoning to their arithmetic. Trapping overflow would throw all that completely out the window. If you want to trap overflow, please use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald < carter.schonwald@gmail.com> wrote:
Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten < merijn@inconsistent.nl> wrote:
> > > > On 8 Feb 2019, at 10:57, Sven Panne
wrote: > > > > Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < > merijn@inconsistent.nl>: > > Our goal is to make "compare NaN n" impossible to happen. [...] > > > > Well, what is supposed to happen then when you *do* see a NaN, > e.g. one produced from a foreign call? You *will* see NaNs in Haskell if > you interact with other languages, most of them take a far less religious > approach to floating points calculations. > > This is not true. As Carter pointed out we can setup the CPU to trap > NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. > Doing this we can simply convert the trap into an exception at the FFI > boundary. > > Now, there are cases were this is problematic, so as said before we > will probably need to allow people to optionally switch on 'value NaNs', > because the foreign code isn't exception safe or for other reasons, but > this is manageable. Via, for example having an annotation on foreign > imports whether you want to trap or not. > > In the scenario where someone switches to value NaNs, we are *still* > not worse off than we are now. The things you suggest already happen *now*, > so the only thing we're advocating is making it possible to have more sane > behaviour in the future. > > Any IEEE-754 compliant implementation of Double that doesn't use > trapping NaN can, by definition, never ever be a sane implementation of > Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't > apply to NaNs and there is *no* safe way to sort/order data containing NaNs. > > I've run into several nasty issues of trying to sort lists > containing NaNs (not just Haskell, also Python and C) and it's *not* just > the NaNs that are affected, entire subsequences end up getting sorted wrong > based on the comparison with NaN and you end up with completely garbled and > unsorted data. > > In other words, there are only two ways to get sane behaviour from > Double with regards to ordering: > > 1. Trapping NaN represenation > 2. Deviate from IEEE-754 semantics > > To me, option 2 is out of the question, it's the one consistent > thing across language we have when it comes to floating point. I understand > that *always* using trap representation isn't feasible, but allowing people > to optionally switch to value NaNs leaves us no worse off than we are > *right now*, and per above, there is literally no way to improve the > situation wrt value NaNs without sacrificing IEEE-754 compliance. > > Cheers, > Merijn > _______________________________________________ > Libraries mailing list > Libraries@haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries > _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Yes, but a ring is sufficient for lots of very basic and important
manipulations. When I'm writing code with Int and Word, I don't even think
about whether the associative and distributive laws apply--I just use them
to simplify my definitions. With trapping overflow, I need to watch for
ranges every time I apply one. Horrible!
On Fri, Feb 8, 2019, 3:05 PM Carter Schonwald I think the algebraic property we usually want for nice integer ish things
is intergral domain. Which is a stronger property than ring. Pardon the
confusion On Fri, Feb 8, 2019 at 3:03 PM Carter Schonwald <
carter.schonwald@gmail.com> wrote: No. A ring can’t have 2x=0 for x not zero. Thus int can’t be And by ring I mean an algebraic structure where you have a multiplicative
group that doesn’t generate zero from products of nonzero elements ... Phrased differently: Int doesn’t have a multiplicative group structure on
the nonzero elements. That makes it a pretty nasty ring. Negate on minBound
should be an overflow exception so you can have actual sane semantics.
This is an old dead horse with lots of blood written about it. https://ghc.haskell.org/trac/ghc/ticket/8695 has some related
discussions On Fri, Feb 8, 2019 at 2:53 PM Jens Blanck minBound + minBound :: Int
0
negate minBound == (minBound :: Int)
True
42 + negate 17 :: Word
25 Int and Word are currently rings. What proportion actually uses them as
such would be interesting to know but I guess it is very small. I wouldn't
dare to reason about Int and Word as rings as there is no guarantee on
which ring they are. Int64 and Word64 and so on; yes, those can be reasoned
about. I'd be very happy to see a separate type for signalling integral types.
Personally, I'd make them the default choice. On Fri, 8 Feb 2019 at 19:27, Carter Schonwald <
carter.schonwald@gmail.com> wrote: I’m not sure if they currently have full ring structure , but I do
agree that trapping and non trapping int and word are useful. Simple example where all the finite signed ints work wrong today : There’s no proper additive inverse for minBound :: int Likewise , what’s our current definition of negate on finite word types? On Fri, Feb 8, 2019 at 2:12 PM David Feuer No, no, no. Int and Word are *rings*, which let's us apply a ton of
mathematical reasoning to their arithmetic. Trapping overflow would throw
all that completely out the window. If you want to trap overflow, please
use different types! On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson <
lennart@augustsson.net wrote: I would *hate* to lose quiet NaNs. They can be very useful. But I’d
be fine having them as a separate type. And while we’re at it, why not make Int overflow and underflow cause
a trap as well? With a different type if you want to wrap. On Fri, Feb 8, 2019 at 08:34 Carter Schonwald <
carter.schonwald@gmail.com> wrote: > Thanks for eloquently summarizing , better than I would , what I
> thought I had laid out.
>
> Ieee floating point has fantastic hardware support . May as well be
> the first real language to actually use it correctly. :)
>
> On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten <
> merijn@inconsistent.nl> wrote:
>
>>
>>
>> > On 8 Feb 2019, at 10:57, Sven Panne _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries _______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Wouldn't both versions throw an exception in that case? Am I missing something? On 2/8/19 2:26 PM, David Feuer wrote:
Yes, but a ring is sufficient for lots of very basic and important manipulations. When I'm writing code with Int and Word, I don't even think about whether the associative and distributive laws apply--I just use them to simplify my definitions. With trapping overflow, I need to watch for ranges every time I apply one. Horrible!
On Fri, Feb 8, 2019, 3:05 PM Carter Schonwald
mailto:carter.schonwald@gmail.com wrote: I think the algebraic property we usually want for nice integer ish things is intergral domain. Which is a stronger property than ring. Pardon the confusion
On Fri, Feb 8, 2019 at 3:03 PM Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: No. A ring can’t have 2x=0 for x not zero. Thus int can’t be
And by ring I mean an algebraic structure where you have a multiplicative group that doesn’t generate zero from products of nonzero elements ...
Phrased differently: Int doesn’t have a multiplicative group structure on the nonzero elements. That makes it a pretty nasty ring. Negate on minBound should be an overflow exception so you can have actual sane semantics. This is an old dead horse with lots of blood written about it.
https://ghc.haskell.org/trac/ghc/ticket/8695 has some related discussions
On Fri, Feb 8, 2019 at 2:53 PM Jens Blanck
mailto:jens.blanck@gmail.com> wrote: > minBound + minBound :: Int 0 > negate minBound == (minBound :: Int) True > 42 + negate 17 :: Word 25
Int and Word are currently rings. What proportion actually uses them as such would be interesting to know but I guess it is very small. I wouldn't dare to reason about Int and Word as rings as there is no guarantee on which ring they are. Int64 and Word64 and so on; yes, those can be reasoned about.
I'd be very happy to see a separate type for signalling integral types. Personally, I'd make them the default choice.
On Fri, 8 Feb 2019 at 19:27, Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: I’m not sure if they currently have full ring structure , but I do agree that trapping and non trapping int and word are useful.
Simple example where all the finite signed ints work wrong today :
There’s no proper additive inverse for minBound :: int
Likewise , what’s our current definition of negate on finite word types?
On Fri, Feb 8, 2019 at 2:12 PM David Feuer
mailto:david.feuer@gmail.com> wrote: No, no, no. Int and Word are *rings*, which let's us apply a ton of mathematical reasoning to their arithmetic. Trapping overflow would throw all that completely out the window. If you want to trap overflow, please use different types!
On Fri, Feb 8, 2019, 2:07 PM Lennart Augustsson
mailto:lennart@augustsson.net wrote: I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
mailto:merijn@inconsistent.nl> wrote: > On 8 Feb 2019, at 10:57, Sven Panne
mailto:svenpanne@gmail.com> wrote: > > Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten mailto:merijn@inconsistent.nl>: > Our goal is to make "compare NaN n" impossible to happen. [...] > > Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations. This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries --
*Vanessa McHale* Functional Compiler Engineer | Chicago, IL Website: www.iohk.io http://iohk.io Twitter: @vamchale PGP Key ID: 4209B7B5 Input Output http://iohk.io Twitter https://twitter.com/InputOutputHK Github https://github.com/input-output-hk LinkedIn https://www.linkedin.com/company/input-output-global This e-mail and any file transmitted with it are confidential and intended solely for the use of the recipient(s) to whom it is addressed. Dissemination, distribution, and/or copying of the transmission by anyone other than the intended recipient(s) is prohibited. If you have received this transmission in error please notify IOHK immediately and delete it from your system. E-mail transmissions cannot be guaranteed to be secure or error free. We do not accept liability for any loss, damage, or error arising from this transmission

On 08/02/2019 21.53, Vanessa McHale wrote:
Wouldn't both versions throw an exception in that case? Am I missing something?
Not necessarily, the classic example would be the Binary Search bug https://thebittheories.com/the-curious-case-of-binary-search-the-famous-bug-... (it could be argued that you really want a *trap* in this case as it would surface the bug, but I'm just confirming that there *can* be different behavior.) Generally: I think it's fine to expect WordNN to do wrap-around arithmetic (and it does form a proper ring), but IntNN is kind of weird because there is that edge case[1] of minBound (as Carter mentioned ITT). IME, usually Word-like types are used for things like crypto, etc. -- not just when you want to enforce "not negative", but that may just be my little bubble. [1] In two's complement which even C++20 is set to mandate!

I absolutely agree. Before any user visible stuff happens the first step
would be rts support for better managing floating point flags / rounding
mode / trap bits.
Could you list some contexts / examples where you want quiet or signaling
nans respectively? The more examples written down and shared the better! :)
On Fri, Feb 8, 2019 at 2:07 PM Lennart Augustsson
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
wrote: Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
wrote: On 8 Feb 2019, at 10:57, Sven Panne
wrote: Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten < merijn@inconsistent.nl>: Our goal is to make "compare NaN n" impossible to happen. [...]
Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations.
This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

On 08/02/2019 20.07, Lennart Augustsson wrote:
I would *hate* to lose quiet NaNs.
This is just getting further off-topic. Nobody is suggesting this, AFACIT. +1 to the original suggestion to just specify totality for Ord (how could it *not* be?) and mention that Double/Float instances are not currently lawful.

Wouldn't having both quiet and signalling NaN types imply wrapping all the primitive operations for one or other type in a CPU state switch? Maybe the compiler could then optimise some away. On 08/02/2019 19:07, Lennart Augustsson wrote:
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
mailto:merijn@inconsistent.nl> wrote: > On 8 Feb 2019, at 10:57, Sven Panne
mailto:svenpanne@gmail.com> wrote: > > Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten mailto:merijn@inconsistent.nl>: > Our goal is to make "compare NaN n" impossible to happen. [...] > > Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations. This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Hey Ganesh,
because of how float stuff works, the code generated will be the same
either way.
On Sun, Feb 10, 2019 at 4:17 PM Ganesh Sittampalam
Wouldn't having both quiet and signalling NaN types imply wrapping all the primitive operations for one or other type in a CPU state switch? Maybe the compiler could then optimise some away.
On 08/02/2019 19:07, Lennart Augustsson wrote:
I would *hate* to lose quiet NaNs. They can be very useful. But I’d be fine having them as a separate type.
And while we’re at it, why not make Int overflow and underflow cause a trap as well? With a different type if you want to wrap.
On Fri, Feb 8, 2019 at 08:34 Carter Schonwald
mailto:carter.schonwald@gmail.com> wrote: Thanks for eloquently summarizing , better than I would , what I thought I had laid out.
Ieee floating point has fantastic hardware support . May as well be the first real language to actually use it correctly. :)
On Fri, Feb 8, 2019 at 5:21 AM Merijn Verstraaten
mailto:merijn@inconsistent.nl> wrote: > On 8 Feb 2019, at 10:57, Sven Panne
mailto:svenpanne@gmail.com> wrote: > > Am Do., 7. Feb. 2019 um 23:31 Uhr schrieb Merijn Verstraaten mailto:merijn@inconsistent.nl>: > Our goal is to make "compare NaN n" impossible to happen. [...] > > Well, what is supposed to happen then when you *do* see a NaN, e.g. one produced from a foreign call? You *will* see NaNs in Haskell if you interact with other languages, most of them take a far less religious approach to floating points calculations. This is not true. As Carter pointed out we can setup the CPU to trap NaNs *even in foreign calls*. So, in theory we CAN rule this out safely. Doing this we can simply convert the trap into an exception at the FFI boundary.
Now, there are cases were this is problematic, so as said before we will probably need to allow people to optionally switch on 'value NaNs', because the foreign code isn't exception safe or for other reasons, but this is manageable. Via, for example having an annotation on foreign imports whether you want to trap or not.
In the scenario where someone switches to value NaNs, we are *still* not worse off than we are now. The things you suggest already happen *now*, so the only thing we're advocating is making it possible to have more sane behaviour in the future.
Any IEEE-754 compliant implementation of Double that doesn't use trapping NaN can, by definition, never ever be a sane implementation of Ord. As IEEE-754 *requires* "NaN /= NaN", so equality symmetry doesn't apply to NaNs and there is *no* safe way to sort/order data containing NaNs.
I've run into several nasty issues of trying to sort lists containing NaNs (not just Haskell, also Python and C) and it's *not* just the NaNs that are affected, entire subsequences end up getting sorted wrong based on the comparison with NaN and you end up with completely garbled and unsorted data.
In other words, there are only two ways to get sane behaviour from Double with regards to ordering:
1. Trapping NaN represenation 2. Deviate from IEEE-754 semantics
To me, option 2 is out of the question, it's the one consistent thing across language we have when it comes to floating point. I understand that *always* using trap representation isn't feasible, but allowing people to optionally switch to value NaNs leaves us no worse off than we are *right now*, and per above, there is literally no way to improve the situation wrt value NaNs without sacrificing IEEE-754 compliance.
Cheers, Merijn _______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org mailto:Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (17)
-
Andrew Butterfield
-
Bardur Arantsson
-
Carter Schonwald
-
chessai .
-
David Feuer
-
Elliot Cameron
-
Ganesh Sittampalam
-
George Wilson
-
Henning Thielemann
-
Herbert Valerio Riedel
-
Jens Blanck
-
Lennart Augustsson
-
Merijn Verstraaten
-
Oliver Charles
-
Sven Panne
-
Tikhon Jelvis
-
Vanessa McHale