<div dir="auto">I believe we should not add a Functor constraint, but for a different reason. One could write<div dir="auto"><br></div><div dir="auto">  data Arr a where</div><div dir="auto">    I :: Unboxed.Vector Int -> Arr Int</div><div dir="auto">    C :: Unboxed.Vector Char -> Arr Char</div><div dir="auto"><br></div><div dir="auto">This has no valid Functor instance, but it has a perfectly sensible Ord1 instance.</div><div dir="auto"><br></div><div dir="auto">As for Map and HashMap, I'd be inclined to remove the "dangerous" instances and add functions (names to be determined) people can use when they know what they're doing. The trouble with the instances is that there's no apparent way to express in the *class* laws what makes an argument valid or invalid. It becomes ad hoc overloading, and I don't think most Haskellers are really into that.</div></div><div class="gmail_extra"><br><div class="gmail_quote">On Mar 15, 2018 7:55 PM, "Oleg Grenrus" <<a href="mailto:oleg.grenrus@iki.fi">oleg.grenrus@iki.fi</a>> wrote:<br type="attribution"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">My hand-wavy intuition:<br>
<br>
Eq witnesses an equality. a -> a -> Bool type isn't enough to guarantee<br>
that,<br>
so we have laws.<br>
<br>
The Eq1 class has member<br>
<br>
    liftEq :: (a -> b -> Bool) -> f a -> f b -> Bool<br>
<br>
the type `a -> b -> Bool` is not an equality decision procedure,<br>
but rather an isomorphism one.<br>
<br>
It looks like for me, that liftEq gives a natural transformation from<br>
`Iso a b` to `Iso (f a) (f b)`. Does this make sense?<br>
<br>
The liftEq2 is the same. We have to think Map as not of<br>
<br>
  Hask * Hask -> Hask (wrong)<br>
<br>
Functor but<br>
<br>
  OrdHask * Hask -> Hask (OrdHask: Ord-types and monotone functions)<br>
<br>
Then, comparing Map k () with Map (Down k) () with \k (Down k') = k == k'<br>
is not well defined, as that "isomorphism candidate" doesn't respect<br>
ordering.<br>
(as an example, for k = Integer, \k (Down k') = k == negate k' would<br>
work, or<br>
even \n m -> n == succ m, for n m :: Integer)<br>
<br>
Similar argument can be used on (Eq k, Hashable k) requirement of<br>
HashMap k v,<br>
with constraints giving an additional Hashable structure. The motivational<br>
example is being able to compare<br>
<br>
    HashMap Text Foo   and   HashMap BusinessId Foo'<br>
<br>
directly, where<br>
 <br>
    newtype BusinessId = BusinessId Text deriving newtype (Eq, Hashable)<br>
<br>
<br>
As Hashable is somewhat arbitrary, I cannot think of other use-cases<br>
(preserving Hashable is next to impossible otherwise then via newtype<br>
deriving).  However, for Map there might be A, B such that `Map A v` and<br>
`Map<br>
B v` are comparable, i.e. there is monotone f :: A -> B, and<br>
<br>
    compareAB a b = f a `compare` b<br>
<br>
which we can use as a first argument for liftCompare2 (Ord2). (There is<br>
mapKeysMonotonic which can be used to achieve the same effect!<br>
unordered-containers could have similar unsafe function too).  That said, I<br>
didn't have such use case myself (yet!?).<br>
<br>
When writing the instances, I was thinking what's (a -> b -> Ordering),<br>
and at this point I have to wave hands even more. I don't know how to<br>
complete<br>
the following sentence<br>
<br>
    The ??? to total order is as isomorphism to equality.<br>
<br>
As a side-note: we have<br>
- `~` witnessing nominal equality<br>
- `Coercible` witnessing structural equality<br>
- It would be very cool to being to say `CoercibleInstance Hashable`,<br>
which is<br>
  satisfied when `Hashable` is `newtype` derived. Is it roles, refining<br>
kinds,<br>
  or something else, I don't know. But I feel it would be useful.  It can be<br>
  used to give `mapKeysMonotonic` a safe type (at least in some cases!)<br>
  Maybe if `Constraint ~ Type`, we could simply require `Coercible (Hashable<br>
  k) (Hashable k')`, but how it would fit the roles?<br>
<br>
So I do agree, that Eq1 f has functorial feel and it's "natural",<br>
this is what its type tells. But if you imply that we should add<br>
`Functor` or<br>
`Bifunctor` super-classes, then I disagree, based on above arguments.<br>
Yes, the functions are unsafe to use (to get meaningful results),<br>
but I see a value for them.<br>
<br>
An example of legitimate (in above sence) instance of Eq1 which isn't a<br>
functor is Eq1 Set. As long as `eq :: a -> b -> Bool` respects the<br>
ordering of<br>
`a` and `b`, we can compare `Set a` with `Set b`.<br>
<Insert a riddle about comparing sets of apples and oranges,<br>
if one can compare apples with oranges, so fruit comparison diagram<br>
commutes><br>
<br>
Cheers, Oleg<br>
<br>
<br>
> I was looking at the Eq2 instances for Data.Map and Data.HashMap, and<br>
> the Eq1 instances for Set and HashSet, and I realized that they're a<br>
> bit ... weird. My instinct is to remove these instances immediately,<br>
> but I figure I should first check with the community (and Oleg, who<br>
> added them to begin with) to make sure they don't make some sort of<br>
> sense I don't understand. In particular, these instances compare keys<br>
> in the order in which they appear in the container. That order may be<br>
> completely unrelated to the given key comparison function.<br>
><br>
> Data.Map example: suppose I have a Map k () and a Map (Down k) (),<br>
> where Down is from Data.Ord. If I call liftEq2 (\x (Down y) -> x == y)<br>
> (==), I will get what looks to me like a totally meaningless result.<br>
><br>
> Data.HashMap example: suppose I have a HashMap Int () and a Hashmap<br>
> String (). If I call liftEq2 (\x y -> show x == y) (==), that won't<br>
> return True even if the strings in the second map are actually the<br>
> results of applying show to the numbers in the first map.<br>
><br>
> Intuitively, I think Eq1 f only makes sense if the shape of f x does<br>
> not depend on the values of type x, and Eq2 p only makes sense if the<br>
> shape of p x y does not depend on the values of types x and y. Is<br>
> there a way to formalize this intuition with class laws? I believe<br>
> that in the case of a Functor, parametricity will guarantee that<br>
><br>
>   liftEq eq (f <$> xs) (g <$> ys) == liftEq (\x y -> eq (f x) (g y)) xs ys<br>
><br>
> Are there *any* legitimate instances of Eq1 or Ord1 that are not<br>
> Functors? Are there *any* legitimate instances of Eq2 or Ord2 that are<br>
> not Bifunctors? My intuition says no. We might wish we could write<br>
> instances for unboxed arrays or vectors, but I believe that is totally<br>
> impossible anyway.<br>
><br>
> David<br>
<br>
<br>
On 15.03.2018 23:48, David Feuer wrote:<br>
> I was looking at the Eq2 instances for Data.Map and Data.HashMap, and<br>
> the Eq1 instances for Set and HashSet, and I realized that they're a<br>
> bit ... weird. My instinct is to remove these instances immediately,<br>
> but I figure I should first check with the community (and Oleg, who<br>
> added them to begin with) to make sure they don't make some sort of<br>
> sense I don't understand. In particular, these instances compare keys<br>
> in the order in which they appear in the container. That order may be<br>
> completely unrelated to the given key comparison function.<br>
><br>
> Data.Map example: suppose I have a Map k () and a Map (Down k) (),<br>
> where Down is from Data.Ord. If I call liftEq2 (\x (Down y) -> x == y)<br>
> (==), I will get what looks to me like a totally meaningless result.<br>
><br>
> Data.HashMap example: suppose I have a HashMap Int () and a Hashmap<br>
> String (). If I call liftEq2 (\x y -> show x == y) (==), that won't<br>
> return True even if the strings in the second map are actually the<br>
> results of applying show to the numbers in the first map.<br>
><br>
> Intuitively, I think Eq1 f only makes sense if the shape of f x does<br>
> not depend on the values of type x, and Eq2 p only makes sense if the<br>
> shape of p x y does not depend on the values of types x and y. Is<br>
> there a way to formalize this intuition with class laws? I believe<br>
> that in the case of a Functor, parametricity will guarantee that<br>
><br>
>   liftEq eq (f <$> xs) (g <$> ys) == liftEq (\x y -> eq (f x) (g y)) xs ys<br>
><br>
> Are there *any* legitimate instances of Eq1 or Ord1 that are not<br>
> Functors? Are there *any* legitimate instances of Eq2 or Ord2 that are<br>
> not Bifunctors? My intuition says no. We might wish we could write<br>
> instances for unboxed arrays or vectors, but I believe that is totally<br>
> impossible anyway.<br>
><br>
> David<br>
<br>
<br>
</blockquote></div></div>