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 <david.feuer@gmail.com> wrote:
Maybe not for everything, but it would hurt `Ord Int` quite a bit.

On Thu, May 7, 2020, 12:52 PM Zemyla <zemyla@gmail.com> 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 <david.feuer@gmail.com> 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