Early feedback: left-biasing `max`

Enough people have spoken up against changing max that I probably won’t continue to pursue it, but for my own curiosity (and for the documentation, if it makes sense to include it): to what end was it designed that way? Why is that an important or useful quality? If I knew that both min and max favored their left argument, and I wanted a pair that was either (x, y) or (y, x), I’d write (min x y, max y x), so it’s not like flipping max would prevent you from easily writing an expression with that property.

It would certainly work to flip the arguments to max. I find it slightly less esthetically pleasing.
But in either case the choice should be clearly documented.

2 Likes

Currently base does 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 (==).

The documentation in base contradict the report and the actual min, max implementation.
Maybe the documentation should be updated (it’s been introduced in 2018, much after the Ord class has been created).
Having said that, apart from Bool (that you could simplify to x <= y) I don`t see the interest of not requiring to return either of the argument.

This statement allows min (Arg 2 "Two", Arg 1 "One") to return Arg 1 "Two" which is obviously inacceptable.

Maybe we should introduce minMax :: a -> a -> (a, a) and define min and max in term of (min = fst . minMax and max = snd . minMax.

1 Like

You could indeed use flip max but why on earth would do that ? I mean unless you read the Ord doc,
(which none of us have done until now) how would you know that min max break the intuition that min and max are dual or antonym work as a pair, however you want to phrase it.
x == min x y <=> y == max x y is the general mathematical intuition . If not, why would it be different ? Because a Foldable type class which been invented 10 years after Ord (or 200 years after the min function) ?

The Report is a document of historical interest only. But how does the documentation contradict the actual implementation? Each instance Ord can define its own.

Because, as you say, they’re dual. In my case, the stronger intuition is that a caveat like ‘in case of ties, the first argument is returned’ would apply consistently to both min and max. Expecting that, if I wanted a pair in sorted order, I would use min x y and max y x to construct that pair.

The intuitions from pure mathematics don’t hold much sway for me here because in pure mathematics, both min and max are symmetric functions and none of this matters. It’s equally true in pure mathematics that x == min x y <=> y == max y x, because in pure mathematics, max x y == max y x. If you favor one of these principles over the other, it can’t be because you’re drawing your intuition from pure mathematics; you’re getting that intuition from some other domain, where min and max are not symmetric.

1 Like

There are many types for which semantical equality does not imply structural one. Arg is just one (and exotic) example, ByteString and Text are more common ones.

1 Like

From stackage

-- 6. @x == y@ = @compare x y == EQ@
-- 7. @min x y == if x <= y then x else y@ = 'True'
-- 8. @max x y == if x >= y then x else y@ = 'True'
...
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

Compare

(8) max x y == if x >= y then x else y

with

max x y = if x <= y then y else x.

One is left biased the other is right based.

Is it ? Is there other case where GHC diverge from the report ?

Maybe but in Arg example I created a 3nd value which is a mix of the 2 arguments and according to the doc is an acceptable behavior.

It is only an intuition, it doesn’t have to be correct.
I am just wondering if you intuition is not biased by the fact you encounter this issue from a Foldable point of view.

I guess I’ll never know for sure, because I only learned about max being right-biased in the context of investigating an inconsistency in the Foldable functions. But I was surprised to learn that max favored the opposite argument to min, and I think I would have been equally surprised to learn that in any other context. It just strikes me as an odd choice in the context of software engineering, where it’s generally preferred that similar things behave similarly. I think that maybe some of you all think that an intrinsic part of max-ness is reaching toward the right, where min-ness reaches toward the left—the argument bias is for some reason coupled to the ordering of the values being compared. I see it as an approximation of the ideal min and max—we can’t have symmetric min and max, so we have to compromise, and I would expect that compromise to be the same for both functions.

It’s all kind of moot; as I said, the support for changing this doesn’t seem consistent enough for me to pursue it, so I’m going to pivot toward making the documentation as clear as possible, and possibly campaign for making the Ord documentation stricter about what min and max should be allowed to return (without changing their default implementation).

1 Like

I think the doc and the implementation should be in sync (and ideally with the report).
However, as the doc has been updated well after the code (and the report) it might be interesting to dig out the discussion relative to that “update” of the doc.

Ah, as for that, I have these links:

Here David Feuer introduces the current wording seemingly off the top of his head:

And here’s the MR where the structural equality vs. Eq-equality question is discussed, but no mention of bias direction:

Given the decision to allow Ord instances to return things that are merely Eq-equal to either argument, the documentation is technically correct because there is no bias up to Eq-equality. The documentation merely suggests a left bias. So nothing really went wrong here. However, in order for maximum to be morally a special case of maximumBy, we really would need to make the requirements on max stronger than Eq-equality. I share your discomfort with the current documentation allowing implementations to return some sort of hybrid of the two arguments; that’s very much not what a function called max should do, in my opinion!

I think the merging of those pull requests would have benefited from a better scrutiny, the doc being confusing at best.

I don’t know the original motivation, but I know plenty of cases when min / max returning something different from their arguments is useful.

  1. Quite often the difference between semantical and structural equality is in some sort of annotation with a provenance / position. E. g.,
data Value = Value { getValue :: Int, getProvenance :: Position }

instance Eq Value where 
  (==) = (==) `on` getValue

Now what is the provenance of min x y :: Value? It might be sensible to set Position to <no location>, or maybe to a position of min itself, or maybe combine position ranges somehow. In all these cases min x y is structurally neither x nor y (but semantically equal to one of them).

  1. Another case is that maybe min / max does not evaluate anything, but just construct a correspondent expression. Say,
data Expr 
  = Const Int 
  | Add Expr Expr 
  | Mul Expr Expr 
  | Min Expr Expr 
  | Max Expr Expr

and then simply

min :: Expr -> Expr -> Expr
min = Min
  1. Further, if evaluation of min / max requires some sort of normalisation of arguments, why would not we return the normalised value? For example, it makes a lot of sense for min (Add (Const 1) (Const 2)) (Const 5) to return Const 3.

A variation of above is the following definition of min for ByteString:

min x y
  | Data.ByteString.null x = mempty
  | otherwise = ...

Even while x == mempty, it is not necessarily structurally equal to it (it might be a zero slice of a larger ByteString). And yet this is a sensible definition, useful to free up some over-retained data.

1 Like

My issue with all three of these points is that they’re general arguments against ever having laws. Imagine, for example, extending Expr to include a primitive for semigroup append:

data Expr
 = ...
 | Append Expr Expr

and then

instance Semigroup Expr where
  (<>) = Append

But this instance violates the associativity law of Semigroup. Is that an argument against having the law?

I don’t find this to be a problematic min. The details of how ByteString is implemented internally shouldn’t matter here, as long as the API for ByteString is explicit about which functions peek behind the curtain and which are respectful of the boundary. I’ve been using the phrase ‘observable equality’ rather than ‘structural equality’ to try to highlight this: the essence of the law I would propose is that for any ‘safe’ f :: a -> Bool, let z = f (min x y) in z == f x || z == f y is always true. Hopefully any functions that can distinguish two empty ByteStrings by looking at what memory regions they slice either are documented as unsafe or wrap their results in IO?

I don’t think so. The laws are just required to hold up to some observation function.

@tomjaguarpaw, I don’t understand the point you’re trying to make. Bodigrim’s argument was, it’s convenient not to require Ord instances to obey a stricter version of its laws, because that allows more instances. My counter is that it’s always convenient in that way not to require instances to obey laws, and yet we have laws. I have no idea what your statement means in that context.

Perhaps it would help if I elaborate. There’s a natural tension between having stronger laws (good because you can prove more) and having more instances (good becaues you can use the class in more situations). One way of having many of the benefits of both worlds is to require laws to hold only up to a fairly fine-grained observation function. I see Bodigrim’s points as general arguments in favour of laws holding up to fairly fine-grained observation functions. (Not that I necessarily agree with that, but I think that’s the strongest conclusion one can derive from his points.) However, you said

My issue with all three of these points is that they’re general arguments against ever having laws.

That seems like far too strong a conclusion to me! Perhaps it would help if you explained how you got there from Bodigrim’s points.

EDIT: Or to put it another way, my interpretation of what you’re saying is “You can’t believe Bodigrim’s points yet also believe in ever having laws”. Did I get that right? If so could you please explain? That’s not obvious to me!