<html><head></head><body>Is there a language feature that could be built that would reduce the cost of inter-package refactors like this in the future?<br><br><div class="gmail_quote">On October 25, 2021 4:06:46 PM UTC, "Hécate" <hecate@glitchbra.in> wrote:<blockquote class="gmail_quote" style="margin: 0pt 0pt 0pt 0.8ex; border-left: 1px solid rgb(204, 204, 204); padding-left: 1ex;">
<pre dir="auto" class="k9mail">Hi Joachim :)<br><br>I will have to express a friendly but firm disagreement on the argument of a<br>"one time cost".<br>You will also have to open PRs for every library, change pedagogical <br>material,<br>broadcast those changes to developers, and provide scripts for code-modding<br>tools in order to automate this on proprietary codebases.<br><br>Side-proposal<br><br>If you really want to break a bunch of things and fix mistake of the past,<br>I would suggest to really go for the throat and have PartialEq, <br>PartialOrd, Eq, and Ord<br><br>We could finally get rid of the Eq instance for the various IEEE types <br>like Double, and promote<br>property testing to the wider public to verify that the laws are indeed <br>respected by the implementations.<br><br><br>module NewClasses where<br><br>import Prelude hiding (Eq(..), Ord(..))<br><br>-- | Equality comparisons which are partial equivalence relations.<br>class PartialEq a where<br>   (==) :: a -> a -> Bool<br><br>-- | Equality comparisons which are equivalence relations.<br>-- It is laws-only and manual implementations would be<br>-- verified through property testing.<br>class PartialEq a => Eq a<br><br>-- | Partial order<br>class PartialEq a => PartialOrd a where<br>   compare' :: a -> a -> Maybe Ordering<br>   (<) :: a -> a -> Bool<br>   (<=) :: a -> a -> Bool<br>   (>) :: a -> a -> Bool<br>   (>=) :: a -> a -> Bool<br><br>-- | Total order<br>class (PartialOrd a, Eq a) => Ord a where<br>   compare :: a -> a -> Ordering<br>   max :: a -> a -> a<br>   min :: a -> a -> a<br><br><br>Cheers,<br>Hécate<br><br>Le 25/10/2021 à 15:22, Joachim Breitner a écrit :<br><blockquote class="gmail_quote" style="margin: 0pt 0pt 1ex 0.8ex; border-left: 1px solid #729fcf; padding-left: 1ex;">Hi,<br><br>ah, yes, let me summarize my main motivation (perf benefits were just a<br>side-benefit I was hoping for):<br><br>You can’t implement (/=) faster than (==) (up to, in the worst case,<br>the cost of a single `not`, which often gets optimized away anyways).<br><br>As such, having (/=) in Eq was a (small) mistake back then, and it’s<br>worth fixing.<br><br>There is one time cost of asking developers to _remove_ code. But code<br>that was probably not worth writing in the first place! And I don’t<br>blame them, the Eq class _invites_ writing that code.<br><br>Then the benefits are twofold:<br>  <br>  * No more awkwards explanations about silly things in the likely first<br>    type class that developers care about.<br><br>  * Less code to read, maintain, compile in all the libraries that _do_<br>    define (/=) right now.<br><br>  * Devs who instantiate Eq in the future will not be tricked into<br>    wondering if they need to implement (/=) and why.<br><br>So even if “helps teaching beginners” doesn’t beat “having to bug<br>maintainers”, then maybe the second point (“saving all develpers time<br>and effort in the future”) does?<br><br>Cheers,<br>Joachim<br></blockquote><br><div class="k9mail-signature">-- <br>Hécate ✨<br>🐦: @TechnoEmpress<br>IRC: Hecate<br>WWW: <a href="https://glitchbra.in">https://glitchbra.in</a><br>RUN: BSD<hr>Libraries mailing list<br>Libraries@haskell.org<br><a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries">http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries</a><br></div></pre></blockquote></div></body></html>