Ord methods are surprisingly strict

Hi! Generally, when using libraries, I expect functions to be as lazy as possible, unless they are documented to have different strictness properties. My impression was that this rule of thumb is fairly widely accepted. If this is not a good rule to work with, please do correct me! In any case, I noticed that many instances of Ord in base are an exception to that rule: (>=), max, etc. tend to evaluate both arguments, although a result could often be produced based on the value of only one argument. For example (True >= x) could return True without evaluating x, but it doesn't. The most blatant and trivial example would be () where the ordering can be determined without looking at any argument. However: $ ghci GHCi, version 8.10.1: https://www.haskell.org/ghc/ :? for help
() >= undefined *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:13:7 in interactive:Ghci1 undefined >= () *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:14:1 in interactive:Ghci1
The code where I first noticed the issue looked a bit like this: data Const = Type | Kind | Sort deriving (Eq, Ord, Show) f :: NonEmpty Const -> Const f = maximum Ideally f would stop traversing the list once it encounters the first Sort. Yet it doesn't:
f (Sort :| [undefined]) *** Exception: Prelude.undefined
Redefining the Ord instance is trickier than expected too: instance Ord Const where Type <= _ = True Kind <= Kind = True Kind <= Sort = True Sort <= Sort = True _ <= _ = False This is insufficient to fix max, since its default implementation is biased towards the second argument: max x y = if x <= y then y else x
max Sort undefined *** Exception: Prelude.undefined
So I customize max: max Type x = x max Kind Sort = Kind max Kind _ = Kind max Sort _ = Sort (f (Sort :| [undefined])) still fails! This turns out be due to NonEmpty's Foldable instance relying on the default definition for maximum: maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . getMax . foldMap (Max #. (Just :: a -> Maybe a)) The problem here is that Maybe's Semigroup instance is strict in both arguments! So I have to define f = foldr1 max …to finally get
f (Sort :| [undefined]) Sort
So my questions are: Why are derived Ord instances and most Ord instances in base so surprisingly strict? How come the entire tooling around Ord seems so biased towards strict Ord implementations? Cheers, Simon

I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks. On Thu, May 7, 2020, 9:03 AM Simon Jakobi via Libraries < libraries@haskell.org> wrote:
Hi!
Generally, when using libraries, I expect functions to be as lazy as possible, unless they are documented to have different strictness properties. My impression was that this rule of thumb is fairly widely accepted. If this is not a good rule to work with, please do correct me!
In any case, I noticed that many instances of Ord in base are an exception to that rule: (>=), max, etc. tend to evaluate both arguments, although a result could often be produced based on the value of only one argument.
For example (True >= x) could return True without evaluating x, but it doesn't.
The most blatant and trivial example would be () where the ordering can be determined without looking at any argument. However:
$ ghci GHCi, version 8.10.1: https://www.haskell.org/ghc/ :? for help
() >= undefined *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:13:7 in interactive:Ghci1 undefined >= () *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:14:1 in interactive:Ghci1
The code where I first noticed the issue looked a bit like this:
data Const = Type | Kind | Sort deriving (Eq, Ord, Show)
f :: NonEmpty Const -> Const f = maximum
Ideally f would stop traversing the list once it encounters the first Sort. Yet it doesn't:
f (Sort :| [undefined]) *** Exception: Prelude.undefined
Redefining the Ord instance is trickier than expected too:
instance Ord Const where Type <= _ = True Kind <= Kind = True Kind <= Sort = True Sort <= Sort = True _ <= _ = False
This is insufficient to fix max, since its default implementation is biased towards the second argument:
max x y = if x <= y then y else x
max Sort undefined *** Exception: Prelude.undefined
So I customize max:
max Type x = x max Kind Sort = Kind max Kind _ = Kind max Sort _ = Sort
(f (Sort :| [undefined])) still fails!
This turns out be due to NonEmpty's Foldable instance relying on the default definition for maximum:
maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . getMax . foldMap (Max #. (Just :: a -> Maybe a))
The problem here is that Maybe's Semigroup instance is strict in both arguments!
So I have to define
f = foldr1 max
…to finally get
f (Sort :| [undefined]) Sort
So my questions are:
Why are derived Ord instances and most Ord instances in base so surprisingly strict?
How come the entire tooling around Ord seems so biased towards strict Ord implementations?
Cheers, Simon _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

No, it's because automatically derived Ord only defines "compare", which is
automatically strict in both arguments because it has to tell EQ from LT or
GT. Then the other methods are defined in terms of that. I don't think
having (<=) et al be potentially lazy would hurt performance much.
On Thu, May 7, 2020, 08:26 David Feuer
I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
On Thu, May 7, 2020, 9:03 AM Simon Jakobi via Libraries < libraries@haskell.org> wrote:
Hi!
Generally, when using libraries, I expect functions to be as lazy as possible, unless they are documented to have different strictness properties. My impression was that this rule of thumb is fairly widely accepted. If this is not a good rule to work with, please do correct me!
In any case, I noticed that many instances of Ord in base are an exception to that rule: (>=), max, etc. tend to evaluate both arguments, although a result could often be produced based on the value of only one argument.
For example (True >= x) could return True without evaluating x, but it doesn't.
The most blatant and trivial example would be () where the ordering can be determined without looking at any argument. However:
$ ghci GHCi, version 8.10.1: https://www.haskell.org/ghc/ :? for help
() >= undefined *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:13:7 in interactive:Ghci1 undefined >= () *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:14:1 in interactive:Ghci1
The code where I first noticed the issue looked a bit like this:
data Const = Type | Kind | Sort deriving (Eq, Ord, Show)
f :: NonEmpty Const -> Const f = maximum
Ideally f would stop traversing the list once it encounters the first Sort. Yet it doesn't:
f (Sort :| [undefined]) *** Exception: Prelude.undefined
Redefining the Ord instance is trickier than expected too:
instance Ord Const where Type <= _ = True Kind <= Kind = True Kind <= Sort = True Sort <= Sort = True _ <= _ = False
This is insufficient to fix max, since its default implementation is biased towards the second argument:
max x y = if x <= y then y else x
max Sort undefined *** Exception: Prelude.undefined
So I customize max:
max Type x = x max Kind Sort = Kind max Kind _ = Kind max Sort _ = Sort
(f (Sort :| [undefined])) still fails!
This turns out be due to NonEmpty's Foldable instance relying on the default definition for maximum:
maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . getMax . foldMap (Max #. (Just :: a -> Maybe a))
The problem here is that Maybe's Semigroup instance is strict in both arguments!
So I have to define
f = foldr1 max
…to finally get
f (Sort :| [undefined]) Sort
So my questions are:
Why are derived Ord instances and most Ord instances in base so surprisingly strict?
How come the entire tooling around Ord seems so biased towards strict Ord implementations?
Cheers, Simon _______________________________________________ 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

Maybe not for everything, but it would hurt `Ord Int` quite a bit.
On Thu, May 7, 2020, 12:52 PM Zemyla
No, it's because automatically derived Ord only defines "compare", which is automatically strict in both arguments because it has to tell EQ from LT or GT. Then the other methods are defined in terms of that. I don't think having (<=) et al be potentially lazy would hurt performance much.
On Thu, May 7, 2020, 08:26 David Feuer
wrote: I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
On Thu, May 7, 2020, 9:03 AM Simon Jakobi via Libraries < libraries@haskell.org> wrote:
Hi!
Generally, when using libraries, I expect functions to be as lazy as possible, unless they are documented to have different strictness properties. My impression was that this rule of thumb is fairly widely accepted. If this is not a good rule to work with, please do correct me!
In any case, I noticed that many instances of Ord in base are an exception to that rule: (>=), max, etc. tend to evaluate both arguments, although a result could often be produced based on the value of only one argument.
For example (True >= x) could return True without evaluating x, but it doesn't.
The most blatant and trivial example would be () where the ordering can be determined without looking at any argument. However:
$ ghci GHCi, version 8.10.1: https://www.haskell.org/ghc/ :? for help
() >= undefined *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:13:7 in interactive:Ghci1 undefined >= () *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:14:1 in interactive:Ghci1
The code where I first noticed the issue looked a bit like this:
data Const = Type | Kind | Sort deriving (Eq, Ord, Show)
f :: NonEmpty Const -> Const f = maximum
Ideally f would stop traversing the list once it encounters the first Sort. Yet it doesn't:
f (Sort :| [undefined]) *** Exception: Prelude.undefined
Redefining the Ord instance is trickier than expected too:
instance Ord Const where Type <= _ = True Kind <= Kind = True Kind <= Sort = True Sort <= Sort = True _ <= _ = False
This is insufficient to fix max, since its default implementation is biased towards the second argument:
max x y = if x <= y then y else x
max Sort undefined *** Exception: Prelude.undefined
So I customize max:
max Type x = x max Kind Sort = Kind max Kind _ = Kind max Sort _ = Sort
(f (Sort :| [undefined])) still fails!
This turns out be due to NonEmpty's Foldable instance relying on the default definition for maximum:
maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . getMax . foldMap (Max #. (Just :: a -> Maybe a))
The problem here is that Maybe's Semigroup instance is strict in both arguments!
So I have to define
f = foldr1 max
…to finally get
f (Sort :| [undefined]) Sort
So my questions are:
Why are derived Ord instances and most Ord instances in base so surprisingly strict?
How come the entire tooling around Ord seems so biased towards strict Ord implementations?
Cheers, Simon _______________________________________________ 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 agree with David here. I’m not sure I see a way to have it be usefully
lazy? Or even soemthing that we can have be consistently so with any
uniformity. Plus could really really mess with certain types of inner
loops we’d hope ghc would specialize etc.
OTOH I could be totally wrong
On Thu, May 7, 2020 at 1:22 PM David Feuer
Maybe not for everything, but it would hurt `Ord Int` quite a bit.
On Thu, May 7, 2020, 12:52 PM Zemyla
wrote: No, it's because automatically derived Ord only defines "compare", which is automatically strict in both arguments because it has to tell EQ from LT or GT. Then the other methods are defined in terms of that. I don't think having (<=) et al be potentially lazy would hurt performance much.
On Thu, May 7, 2020, 08:26 David Feuer
wrote: I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
On Thu, May 7, 2020, 9:03 AM Simon Jakobi via Libraries < libraries@haskell.org> wrote:
Hi!
Generally, when using libraries, I expect functions to be as lazy as possible, unless they are documented to have different strictness properties. My impression was that this rule of thumb is fairly widely accepted. If this is not a good rule to work with, please do correct me!
In any case, I noticed that many instances of Ord in base are an exception to that rule: (>=), max, etc. tend to evaluate both arguments, although a result could often be produced based on the value of only one argument.
For example (True >= x) could return True without evaluating x, but it doesn't.
The most blatant and trivial example would be () where the ordering can be determined without looking at any argument. However:
$ ghci GHCi, version 8.10.1: https://www.haskell.org/ghc/ :? for help
() >= undefined *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:13:7 in interactive:Ghci1 undefined >= () *** Exception: Prelude.undefined CallStack (from HasCallStack): error, called at libraries/base/GHC/Err.hs:79:14 in base:GHC.Err undefined, called at <interactive>:14:1 in interactive:Ghci1
The code where I first noticed the issue looked a bit like this:
data Const = Type | Kind | Sort deriving (Eq, Ord, Show)
f :: NonEmpty Const -> Const f = maximum
Ideally f would stop traversing the list once it encounters the first Sort. Yet it doesn't:
f (Sort :| [undefined]) *** Exception: Prelude.undefined
Redefining the Ord instance is trickier than expected too:
instance Ord Const where Type <= _ = True Kind <= Kind = True Kind <= Sort = True Sort <= Sort = True _ <= _ = False
This is insufficient to fix max, since its default implementation is biased towards the second argument:
max x y = if x <= y then y else x
max Sort undefined *** Exception: Prelude.undefined
So I customize max:
max Type x = x max Kind Sort = Kind max Kind _ = Kind max Sort _ = Sort
(f (Sort :| [undefined])) still fails!
This turns out be due to NonEmpty's Foldable instance relying on the default definition for maximum:
maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . getMax . foldMap (Max #. (Just :: a -> Maybe a))
The problem here is that Maybe's Semigroup instance is strict in both arguments!
So I have to define
f = foldr1 max
…to finally get
f (Sort :| [undefined]) Sort
So my questions are:
Why are derived Ord instances and most Ord instances in base so surprisingly strict?
How come the entire tooling around Ord seems so biased towards strict Ord implementations?
Cheers, Simon _______________________________________________ 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

Am Do., 7. Mai 2020 um 15:26 Uhr schrieb David Feuer : I believe this is all about strictness analysis. If these were lazy, then
users would have to be very careful to force the lazy arguments when they
don't need that laziness to avoid building unnecessary thunks. This argument holds basically for every potentially lazy function, and I
fail to see why comparisons should be special, so this is not really
convincing. :-) We have easy ways to make things more strict, but not the
other way around.
In any case, it has historically been the case that the reference
implementations in the Haskell language/library report define the
strictness of the defined functions, too. Otherwise things could be very
surprising, in both ways (too lazy, too strict). Furthermore, the report is
*very* explicit about the derived instances:
https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000...
And
(), Bool, ... are defined via deriving:
https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009

If one of my applications develops a memory leak because of this potential
change, where should I invoice you for the time wasted tracking down &
fixing it? My short-term contract rate is $250/hour but I could be argued
down to $200/hour.
On May 7, 2020, at 1:00 PM, Sven Panne : I believe this is all about strictness analysis. If these were lazy, then
users would have to be very careful to force the lazy arguments when they
don't need that laziness to avoid building unnecessary thunks. This argument holds basically for every potentially lazy function, and I
fail to see why comparisons should be special, so this is not really
convincing. :-) We have easy ways to make things more strict, but not the
other way around.
In any case, it has historically been the case that the reference
implementations in the Haskell language/library report define the
strictness of the defined functions, too. Otherwise things could be very
surprising, in both ways (too lazy, too strict). Furthermore, the report is
*very* explicit about the derived instances:
https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000...
And
(), Bool, ... are defined via deriving:
https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009
_______________________________________________
Libraries mailing list
Libraries@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

Christopher, seeing how the discussion goes, I don't think we want to change anything... On 2020-05-07 20:53, Christopher Allen wrote:
If one of my applications develops a memory leak because of this potential change, where should I invoice you for the time wasted tracking down & fixing it? My short-term contract rate is $250/hour but I could be argued down to $200/hour.
On May 7, 2020, at 1:00 PM, Sven Panne
mailto:svenpanne@gmail.com> wrote: Am Do., 7. Mai 2020 um 15:26 Uhr schrieb David Feuer
mailto:david.feuer@gmail.com>: I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
This argument holds basically for every potentially lazy function, and I fail to see why comparisons should be special, so this is not really convincing. :-) We have easy ways to make things more strict, but not the other way around.
In any case, it has historically been the case that the reference implementations in the Haskell language/library report define the strictness of the defined functions, too. Otherwise things could be very surprising, in both ways (too lazy, too strict). Furthermore, the report is *very* explicit about the derived instances: https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000... And (), Bool, ... are defined via deriving: https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009 _______________________________________________ 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

Even aside from the memory leak potential and the performance degradation
from allocation, adding extra tests will degrade performance in typical
cases for many types. Comparing against minBound/maxBound isn't always
free. For a simple Int comparison, that's an extra compare and conditional
jump every time. For such a fundamental operation, that's a big ouch!
On Thu, May 7, 2020, 2:53 PM Christopher Allen
If one of my applications develops a memory leak because of this potential change, where should I invoice you for the time wasted tracking down & fixing it? My short-term contract rate is $250/hour but I could be argued down to $200/hour.
On May 7, 2020, at 1:00 PM, Sven Panne
wrote: Am Do., 7. Mai 2020 um 15:26 Uhr schrieb David Feuer < david.feuer@gmail.com>:
I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
This argument holds basically for every potentially lazy function, and I fail to see why comparisons should be special, so this is not really convincing. :-) We have easy ways to make things more strict, but not the other way around.
In any case, it has historically been the case that the reference implementations in the Haskell language/library report define the strictness of the defined functions, too. Otherwise things could be very surprising, in both ways (too lazy, too strict). Furthermore, the report is *very* explicit about the derived instances: https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000... And (), Bool, ... are defined via deriving: https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009 _______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries

I figured the biggest wins on lazy <= et al would come from ADTs with two
constructors with at least one nullary. Bool, Maybe, and [] all qualify.
And generally, with operations that can potentially be lazy in either
argument, the convention is that it's in the first argument.
Also, there is at least one compelling reason for the comparison operators
to be lazy. Take the infinite search monad:
newtype Search r a = Search { find :: (a -> r) -> a }
It has an Alt instance for finding the better of two results with a given
valuation function:
instance Ord r => Alt (Search r) where
Search ma Search mb = Search $ \p -> let
a = ma p
b = mb p
in if p a >= p b then a else b
For Search Bool, which uses a predicate as its valuation function, this
means that, if p a is True, it doesn't need to evaluate b or p b at all.
On Thu, May 7, 2020, 14:00 David Feuer
Even aside from the memory leak potential and the performance degradation from allocation, adding extra tests will degrade performance in typical cases for many types. Comparing against minBound/maxBound isn't always free. For a simple Int comparison, that's an extra compare and conditional jump every time. For such a fundamental operation, that's a big ouch!
On Thu, May 7, 2020, 2:53 PM Christopher Allen
wrote: If one of my applications develops a memory leak because of this potential change, where should I invoice you for the time wasted tracking down & fixing it? My short-term contract rate is $250/hour but I could be argued down to $200/hour.
On May 7, 2020, at 1:00 PM, Sven Panne
wrote: Am Do., 7. Mai 2020 um 15:26 Uhr schrieb David Feuer < david.feuer@gmail.com>:
I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
This argument holds basically for every potentially lazy function, and I fail to see why comparisons should be special, so this is not really convincing. :-) We have easy ways to make things more strict, but not the other way around.
In any case, it has historically been the case that the reference implementations in the Haskell language/library report define the strictness of the defined functions, too. Otherwise things could be very surprising, in both ways (too lazy, too strict). Furthermore, the report is *very* explicit about the derived instances: https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000... And (), Bool, ... are defined via deriving: https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009 _______________________________________________ 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. Mai 2020 um 20:53 Uhr schrieb Christopher Allen < cma@bitemyapp.com>:
If one of my applications develops a memory leak because of this potential change, where should I invoice you for the time wasted tracking down & fixing it? My short-term contract rate is $250/hour but I could be argued down to $200/hour.
Sorry if I was unclear: I didn't propose to change the strictness of the Ord instances for the Prelude types, quite the opposite: As I said (with reference to the report), they are basically carved in stone. If someone wants lazier instances, they would e.g. have to use a newtype wrapper + new Ord instances. And they should better document the unusual strictness clearly...

Someone who knows the lore. Thanks for the enlightening references! Another reason for <= to be strict is symmetry. Why would False <= undefined = True be preferable to undefined <= True = True ? And we cannot have both. The natural assumption is that neither of these hold. That said, my self-defined instances of Ord are usually not that strict. --Andreas On 2020-05-07 20:00, Sven Panne wrote:
Am Do., 7. Mai 2020 um 15:26 Uhr schrieb David Feuer
mailto:david.feuer@gmail.com>: I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
This argument holds basically for every potentially lazy function, and I fail to see why comparisons should be special, so this is not really convincing. :-) We have easy ways to make things more strict, but not the other way around.
In any case, it has historically been the case that the reference implementations in the Haskell language/library report define the strictness of the defined functions, too. Otherwise things could be very surprising, in both ways (too lazy, too strict). Furthermore, the report is *very* explicit about the derived instances: https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000... And (), Bool, ... are defined via deriving: https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009

Sven,
Many thanks for the reference to the Haskell report! Looks like it's
high time for me to finally read it! :)
I think it would be good to reproduce the bits regarding the
strictness of derived instances of Eq and Bool in the base haddocks.
What's still unclear to me is whether library authors are expected to
follow the same strictness semantics in their Ord instances. For
example, if I were to expose my Const type with its lazy Ord instance
from a library, would that be surprising for users of the library?
Could someone illustrate in what kind of issues the reduced strictness
might manifest?
Thanks,
Simon
Am Do., 7. Mai 2020 um 20:00 Uhr schrieb Sven Panne
Am Do., 7. Mai 2020 um 15:26 Uhr schrieb David Feuer
: I believe this is all about strictness analysis. If these were lazy, then users would have to be very careful to force the lazy arguments when they don't need that laziness to avoid building unnecessary thunks.
This argument holds basically for every potentially lazy function, and I fail to see why comparisons should be special, so this is not really convincing. :-) We have easy ways to make things more strict, but not the other way around.
In any case, it has historically been the case that the reference implementations in the Haskell language/library report define the strictness of the defined functions, too. Otherwise things could be very surprising, in both ways (too lazy, too strict). Furthermore, the report is *very* explicit about the derived instances: https://www.haskell.org/onlinereport/haskell2010/haskellch11.html#x18-183000... And (), Bool, ... are defined via deriving: https://www.haskell.org/onlinereport/haskell2010/haskellch9.html#x16-1710009

Am Fr., 8. Mai 2020 um 12:56 Uhr schrieb Simon Jakobi < simon.jakobi@googlemail.com>:
[...] What's still unclear to me is whether library authors are expected to follow the same strictness semantics in their Ord instances. For example, if I were to expose my Const type with its lazy Ord instance from a library, would that be surprising for users of the library?
IMHO it would be a bit surprising, as a general rule of thumb: Everything which is done differently from the way base/Prelude does it is surprising. It's not necessarily wrong, but at least it needs some prominent documentation, including the reasoning behind it.
Could someone illustrate in what kind of issues the reduced strictness might manifest?
In short: * too strict: non-termination * too lazy: space leaks
participants (7)
-
Andreas Abel
-
Carter Schonwald
-
Christopher Allen
-
David Feuer
-
Simon Jakobi
-
Sven Panne
-
Zemyla