core-libraries-committee icon indicating copy to clipboard operation
core-libraries-committee copied to clipboard

Rationalize tie-breaking behavior of `max`, `maximum`, `maximumBy`, etc.

Open rhendric opened this issue 2 years ago • 21 comments

Elsewhere:

  • https://gitlab.haskell.org/ghc/ghc/-/issues/15921
  • https://mail.haskell.org/pipermail/libraries/2018-December/029299.html

This is a visible behavior of a base function, though, and so my understanding is that the current best approach for pursuing change is to bring it to the CLC.

In short: base contains (at least) the following ways to get the maximum/minimum of a sequence of values:

{-# LANGUAGE OverloadedLists #-}

import Prelude hiding (foldr1)

import Data.Foldable (maximum, maximumBy, minimum, minimumBy)
import Data.Foldable1 (foldl1', foldMap1, foldr1)
import Data.List.NonEmpty (NonEmpty)
import Data.Semigroup (Arg(..), Max(..), Min(..))

vals :: NonEmpty (Arg Int Int)
vals = [Arg 1 0, Arg 2 3, Arg 2 2, Arg 1 1]

main = do
  print $ foldMap1 Max vals      == Max (Arg 2 3)
  print $ foldl1' max vals       ==      Arg 2 3
  print $ foldr1 max vals        ==      Arg 2 3
  print $ maximum vals           ==      Arg 2 3
  print $ maximumBy compare vals ==      Arg 2 2 -- !!!
  
  print $ foldMap1 Min vals      == Min (Arg 1 0)
  print $ foldl1' min vals       ==      Arg 1 0
  print $ foldr1 min vals        ==      Arg 1 0
  print $ minimum vals           ==      Arg 1 0
  print $ minimumBy compare vals ==      Arg 1 0

maximumBy stands alone in its decision to return a later list element if, according to the comparison function given, it is equal to the extremum seen so far.

This inconsistency is awkward—in particular, it's disturbing for maximumBy compare not to be equivalent to maximum in all cases—and I'd like to formally propose resolving it by making maximumBy left-biased as well.

(All of the above applies equally to Data.Foldable.maximumBy and Data.Foldable1.maximumBy.)

rhendric avatar Aug 11 '23 22:08 rhendric

maximum uses max, which for Arg is defined as

-- | @since 4.9.0.0
instance Ord a => Ord (Arg a b) where
  Arg a _ `compare` Arg b _ = compare a b
  min x@(Arg a _) y@(Arg b _)
    | a <= b    = x
    | otherwise = y
  max x@(Arg a _) y@(Arg b _)
    | a >= b    = x
    | otherwise = y

i.e. Arg instance is left-biased, but it's arbitrary, as default Ord implementation is right biased for max and left biased for min.

class  (Eq a) => Ord a  where
   ...
   max x y = if x <= y then y else x
   min x y = if x <= y then x else y

in other words making maximumBy compare be equivalent to maximum needs a bit more thought, potentially a specification of what min and max should return.

E.g. with

data MyArg a b = MyArg a b deriving Show
instance Eq a => Eq (MyArg a b) where MyArg x _ == MyArg y _ = x == y
instance Ord a => Ord (MyArg a b) where MyArg x _ `compare` MyArg y _ = compare x y

myvals = [MyArg 1 0, MyArg 2 3, MyArg 2 2, MyArg 1 1] :: [MyArg Int Int]

I get

>>> maximum myvals
MyArg 2 2
>>> maximumBy compare myvals
MyArg 2 2

i.e. it's Args, max implementation which makes maximum be left biased!


If you really care about the actual element returned, I'd suggest using foldMap1' with your own max-like function. Then you'll have full control and not rely on unspecified behaviour.

phadej avatar Aug 12 '23 14:08 phadej

Excellent points, thanks. I agree this needs more thought and more detail, and I'll come back with the latter once I've produced the former.

rhendric avatar Aug 12 '23 20:08 rhendric

Beginning again: some users, myself included, are surprised that the following facts hold in combination:

  • The default implementation of max is right-biased
  • The default implementation of min is left-biased
  • The implementation of maximumBy is right-biased regardless of Ord instance
  • Resp. minimumBy, left-biased
  • The implementations of max and min in Ord (Down a) are written assuming a right-biased max and a left-biased min in Ord a, and upholds these biases in its own implementation (as this body recommended in #23)
  • The implementation of max in Ord (Arg a b) is left-biased
  • None of this is documented at all (in fact, if anything, points (7.) and (8.) in the documentation of Ord might lead a half-attentive reader to believe that min and max are both left-biased)

My personal preferences, in descending order, for this situation would be:

  1. A documented principle, consistently applied, of left-biasing min and max and related functions like maximumBy, etc. (changes: default max, maximumBy, Ord (Down a))
  2. A documented principle, consistently applied, of left-biasing min etc. and right-biasing max etc. (changes: Ord (Arg a b))
  3. A documented principle, inconsistently applied but with exceptions documented, of the previous (no code changes, but documenting everything that's surprising, including how and why Arg is special)
  4. The status quo: an undocumented principle, inconsistently applied

The big question for me is whether (1.) is something the CLC would consider. The Haskell 2010 Language Report, section 6.3.2, says the following about max and min:

-- 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

Other than that comment, the report doesn't appear to give any justification for why this particular implementation of max and min is best. The law (?) given in the comment is pleasingly symmetric, but it could have been just as symmetric with two left-biased implementations if written as (min x y, max y x) = (x,y) or (y,x). And in any case, the documentation for Ord in base has, as far back as I could see online, not included this law, which suggests that it doesn't apply to this version of the Haskell world. I also don't know why said documentation excludes this, or replaces it with the more liberal up-to-Eq-equality min and max laws that are there currently.

In the absence of a solid justification for right-biasing max other than tradition, I think it's clear that left-biasing both min and max would be less of a cognitive burden for users to support, in principle. In practice, there might be specific pitfalls to avoid. One such that occurred to me is the case of floating-point Ord instances—while we seem to have a gentleperson's agreement with Ord Float and Ord Double to look the other way as far as NaNs are concerned, there exist functions such as clamp that use max and make explicit guarantees about propagation of NaN, and for such functions it's important to preserve the NaN-propagation properties of the current default max. Fortunately, max x y = if x < y then y else x is both left-biased and has said NaN-propagation properties. (It is also equivalent in performance to the current default, assuming either that the default (<) is used or that a specified (<) is equivalent in cost to (<=), and does not change the minimal complete definition sets of Ord.)

Are there other important areas to consider if proposing a left-biased max? Or is a change like that too radical for the CLC to consider under any circumstances?

rhendric avatar Aug 14 '23 19:08 rhendric

I'd never heard of clamp, it seems it was introduced in base-4.16 but it doesn't have a @since annotation.


I think a well-documented left bias for both min and max would be the best-case scenario, but I'm afraid this kind of change is very subtle. It's difficult to measure how much real-world code implicitly relies on the existing behaviour; that being said, it's trivial to write a local function that retains the right-biased behaviour if a program depends on it. It's the kind of change I'd want to make, but to also make a large fuss about in the forums. It's also the case that many of the existing Prelude functions are left-biased, though by and large for laziness reasons., so bringing max and friends in line with this reinforces that intuition.

mixphix avatar Aug 14 '23 20:08 mixphix

Should I wait for more people to weigh in, or should I now be doing some or all of:

  • flesh general approach (1.) out into a more detailed proposal
  • prepare a draft MR against GHC
  • try to attract attention on Discourse

rhendric avatar Aug 21 '23 20:08 rhendric

  • try to attract attention on Discourse

I'd appreciate if you try this first, thanks!

Bodigrim avatar Aug 22 '23 23:08 Bodigrim

...and for such functions it's important to preserve the NaN-propagation properties of the current default max

Current behavior of max is not IEEE-754-compliant, see the discussion for instance Ord Double under https://ghc.gitlab.haskell.org/ghc/doc/libraries/base-4.19.0.0-inplace/Prelude.html#t:Double.


I'm not convinced by Arg as a motivating example. The results are not distinguishable by instance Eq Arg, and I don't see why we would impose a stricter notion of equality for this partiular case but not in others.

Fundamentally, the current implementation of instance Semigroup (Max a) via (<=) is wrong. It should really use max, because, as a separate member of class Ord, max might have different performance and laziness properties from (<=).

Bodigrim avatar Aug 24 '23 22:08 Bodigrim

Current behavior of max is not IEEE-754-compliant, see the discussion for instance Ord Double under https://ghc.gitlab.haskell.org/ghc/doc/libraries/base-4.19.0.0-inplace/Prelude.html#t:Double.

Yeah, that statement isn't about making these operations IEEE (there's a package for that, as I understand it); I brought up NaN propagation only because, IEEE or not, it's a place in the API where users are especially likely to have done some specific fiddly coding to get the behavior they want based on what they observe base does, not based on some standard. I don't want anyone to have to redo that work because we changed max.

I'm not convinced by Arg as a motivating example. The results are not distinguishable by instance Eq Arg, and I don't see why we would impose a stricter notion of equality for this partiular case but not in others.

I don't want Arg to be the motivating example; it's just the most visible place in base where Eq equality is distinct from observational equality.

The motivation for all of this remains maximum and maximumBy—why do these functions favor (by default in the former case, always in the latter case) values from the end of the Foldable when their companions minimum and minimumBy favor values from the start?

Fundamentally, the current implementation of instance Semigroup (Max a) via (<=) is wrong. It should really use max

It... already does?

But actually, I floated a notion today on Discourse that I'm starting to like, if the right bias of max is something we want to (or think we must) keep. The idea would be to encourage all Ord instances to right-bias max (including Arg), but encourage operations on Foldables to be consistently left-biased—meaning Semigroup (Max a) would be changed to use flip max on the assumption that max is right-biased. That change would make the default maximum left-biased, as it uses Max, and then changing the implementation of maximumBy to be left-biased to match would be the natural choice. (The specialized GHC.List.maximum uses max, so I'd change that to flip max too.) Any code currently folding through Max (Arg ...) would not notice a change, as the two changes to Semigroup (Max a) and Ord (Arg a b) would cancel out.

rhendric avatar Aug 24 '23 23:08 rhendric

CLC-specific question: is it true that the impact assessment process described here only runs builds, not test suites, of the covered packages, and thus wouldn't be suitable for smoke testing the sorts of changes I'm considering here? If so, is there a simple way to tweak the process to run tests too or should I look for my own approach (maybe curator would be suitable)?

rhendric avatar Aug 27 '23 23:08 rhendric

CLC-specific question: is it true that the impact assessment process described here only runs builds, not test suites, of the covered packages, and thus wouldn't be suitable for smoke testing the sorts of changes I'm considering here?

True.

If so, is there a simple way to tweak the process to run tests too or should I look for my own approach (maybe curator would be suitable)?

If you find a simple way to run tests please share :) It should be possible to replicate the way how Stackage server runs them, but it's likely to require some work to reproduce it locally.

Bodigrim avatar Nov 05 '23 17:11 Bodigrim

Back to the topic, there was a fruitful and extensive discussion at https://discourse.haskell.org/t/early-feedback-left-biasing-max/7392/76.

Documentation of class Ord explicitly and unamibguously says that min / max are not expected to be left- or -right-biased:

Note that (7.) and (8.) do not require min and max to return either of their arguments. The result is merely required to equal one of the arguments in terms of (==).

I do not see a strong reason to require structural equality, because normally all class laws in Haskell are up to (==) only. See also https://discourse.haskell.org/t/early-feedback-left-biasing-max/7392/76 for the discussion why the current definition of min / max is useful in many areas.

Further, if vanilla min / max are not required to be left- or -right-biased, it makes even less sense to expect it from minimum / maximum / minimumBy / maximumBy. Thus, I'm negative on the proposed amendments.


@rhendric how would you like to proceed? If you'd like to pursue the topic, it would be great to write down a specific proposal with all required changes.

Bodigrim avatar Nov 05 '23 20:11 Bodigrim

At this point, I would summarize the conversation as follows:

  • A significant number of users are attached to the expectation that (x `min` y, x `max` y) is observationally equivalent to either (x, y) or (y, x) (despite it not being supported by current documented laws or some rare Ord instances like Arg), and this expectation is not consistent with changing the default bias of either min or max.
  • A significant number of users, exemplified by @Bodigrim's most recent comments, are attached to the expectation that min and max don't carry any guarantees about observational equivalence, and this expectation is not consistent with promoting the above expectation to the status of a documented law.
  • Without clarity on whether any sort of observational equivalence relation should or should not be expected from min or max, I agree that it doesn't make sense to expect any similar properties from the related Foldable members.

I am reluctantly forced to accept that the only change that can be made without disrupting anyone's closely-held expectations is to leave all code as-is and document the state of affairs more clearly (as was suggested by wiser people several months ago):

  • that min and max often, but not always, satisfy (x `min` y, x `max` y) = (x, y) or (y, x) as an observational equivalence;
  • that Arg is a type that does not obey this optional relation;
  • that (contrary to some of the existing documentation) minimum/maximum are not special cases of minimumBy/maximumBy, but have their own semantics which users must grapple with on a per-Ord-instance and per-Foldable-instance basis;
  • and that all of this is a considered choice and unlikely to change.

I take little joy in reaching this conclusion, so I haven't gotten around to it yet, but I do intend to submit an MR with the documentation changes I think would be most helpful, at which point I think that MR will more or less be the specific proposal.

rhendric avatar Nov 06 '23 03:11 rhendric

I am reluctantly forced to accept that the only change that can be made without disrupting anyone's closely-held expectations

There seems to be an assumption that only proposals which do not disrupt anyone's expectations are to pass. This is not necessarily so, CLC can accept and has accepted in the past controversial proposals. The only way to progress is to challenge status quo, and I'd like to encourage you to do so.

A significant number of users, exemplified by @Bodigrim's most recent comments, are attached to the expectation that min and max don't carry any guarantees about observational equivalence

It's not like I'm attached to a strong personal belief about max, it's just that the existing documentation says so. There is a difference between "the semantics of max is un(der)specified w.r.t. bias" and "the semantics of max is specified and declares that bias can vary from instance to instance". We might still decide to change even in the latter case, but it's a higher bar.

  • that min and max often, but not always, satisfy (x `min` y, x `max` y) = (x, y) or (y, x) as an observational equivalence;

(I assume you call "observational equivalence" what I call "structural equality") I'm not sure how useful is to say that something holds "often but not always", and I think it might be more confusing than helpful for readers. Are we saying that we'd like to "encourage" instances to satisfy this property? Why? Surely we do not want to promote sortTuple (a, b) = (min a b, max a b) over sortTuple (a, b) = if a < b then (a, b) else (b, a), the latter is a better style and much clearer.

Bodigrim avatar Nov 06 '23 19:11 Bodigrim

This is a tough nut to crack. To have documented the biasing principles when the typeclass was initially designed would have been ideal. Changing existing implementations might lead to bugs that can't be caught by the type checker. However, I think with improved documentation and a good attempt at ironing out at least the instances in base to be in line with the choice of bias, whatever that ends up being, will improve the "aroma" of the Ord typeclass.

mixphix avatar Nov 07 '23 22:11 mixphix

@rhendric if there is no further progress, I'll close this as abandoned by the end of January.

Bodigrim avatar Jan 09 '24 00:01 Bodigrim

Please consider this MR as my proposal: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/11941

rhendric avatar Jan 19 '24 05:01 rhendric

Can this be reopened? I was given the end of January as a deadline, and I submitted the MR in time for that.

rhendric avatar Feb 19 '24 21:02 rhendric

Whoops, I'm terribly sorry, apparently I fat-fingered the wrong button. Reopening.

Bodigrim avatar Feb 21 '24 20:02 Bodigrim

Historical reason for how max/min is defined in Prelude is a Minimal-Pragma {-# MINIMAL compare | (<=) #-} , most everyone custom instance of Ord defines (<=) function, so using (<=) is a cheapest and fastest function:

class  (Eq a) => Ord a  where
   ....
    {-# MINIMAL compare | (<=) #-}

So, we could not to redefine default max , but add 4 new functions into Data.Ord:

maxRight :: Ord a => a -> a -> a
maxRight x y = if x <= y then y else x

maxLeft :: Ord a => a -> a -> a
maxLeft x y = if y <= x then x else y

minRight :: Ord a => a -> a -> a
minRight x y = if y <= x then y else x

minLeft :: Ord a => a -> a -> a
minLeft x y = if x <= y then x else y

VitWW avatar Feb 27 '24 20:02 VitWW

It appears that the MR contains only documentation changes. Per the README:

The primary responsibility of CLC is to manage API changes of base package. The ownership of base belongs to GHC developers, and they can maintain it freely without CLC involvement as long as changes are invisible to clients. Changes which affect performance or laziness and similar are deemed visible. Documentation changes normally fall under GHC developers purview, except significant ones (e. g., adding or changing type class laws).

I see no reason to delay these helpful comments from making it into the next release. @Bodigrim shall we call a vote, or alert the GHC devs that the patch can be merged without our vote?

mixphix avatar Mar 22 '24 15:03 mixphix

Documentation changes normally fall under GHC developers purview, except significant ones (e. g., adding or changing type class laws).

Relevant to this sentence, don't miss this paragraph I'm suggesting adding to Ord:

https://gitlab.haskell.org/ghc/ghc/-/blob/2fd7bfdd35bf7ee62fbdea38ff3de8f1b05c2f8c/libraries/ghc-prim/GHC/Classes.hs#L326-336

It's not adding or changing a law, exactly, but it's giving law-adjacent direction to implementers. Most of the rest of this patch I wouldn't bother the CLC with but this paragraph is on the line, I think.

rhendric avatar Mar 22 '24 19:03 rhendric

I've commented in the MR; I think with a slightly different choice of words we can avoid a CLC vote.

Bodigrim avatar May 10 '24 20:05 Bodigrim

After carefully reviewing the final version of the MR, I don't think it requires a CLC vote. Thanks for your work and persistence @rhendric.

(Technically I have to mark this as "out-of-scope", but it does not mean that I don't appreciate it)

Bodigrim avatar May 23 '24 20:05 Bodigrim