Proposal: Make Eq type class single method
Richard Eisenberg
lists at richarde.dev
Mon Oct 25 21:02:48 UTC 2021
I will also offer my own counter-proposal to intrinsic-superclasses, at https://gitlab.haskell.org/ghc/ghc/-/wikis/instance-templates.
These all predate our current proposals process.
I believe they were all conceived to solve the Applicative/Monad problem (for those of you who weren't around then: Applicative was not always a superclass of Monad), and I'm not sure they will work perfectly here: we might need to make a new class, say, Equality and keep the current Eq as a subclass.
Do look at the proposals, but your mileage may vary.
Richard
> On Oct 25, 2021, at 4:50 PM, Hécate <hecate at glitchbra.in> wrote:
>
> There are the DefaultSuperclassInstances and Intrinsic Superclasses which aim to provide in-compiler support for such transitions:
>
> https://gitlab.haskell.org/ghc/ghc/-/wikis/intrinsic-superclasses <https://gitlab.haskell.org/ghc/ghc/-/wikis/intrinsic-superclasses>
>
> But also code-modding would benefit from being used here, and maybe retrie (https://hackage.haskell.org/package/retrie <https://hackage.haskell.org/package/retrie>)
> would benefit from being used at scale?
>
>
>
> Le 25/10/2021 à 19:05, Ryan Trinkle a écrit :
>> Is there a language feature that could be built that would reduce the cost of inter-package refactors like this in the future?
>>
>> On October 25, 2021 4:06:46 PM UTC, "Hécate" <hecate at glitchbra.in> <mailto:hecate at glitchbra.in> wrote:
>> Hi Joachim :)
>>
>> I will have to express a friendly but firm disagreement on the argument of a
>> "one time cost".
>> You will also have to open PRs for every library, change pedagogical
>> material,
>> broadcast those changes to developers, and provide scripts for code-modding
>> tools in order to automate this on proprietary codebases.
>>
>> Side-proposal
>>
>> If you really want to break a bunch of things and fix mistake of the past,
>> I would suggest to really go for the throat and have PartialEq,
>> PartialOrd, Eq, and Ord
>>
>> We could finally get rid of the Eq instance for the various IEEE types
>> like Double, and promote
>> property testing to the wider public to verify that the laws are indeed
>> respected by the implementations.
>>
>>
>> module NewClasses where
>>
>> import Prelude hiding (Eq(..), Ord(..))
>>
>> -- | Equality comparisons which are partial equivalence relations.
>> class PartialEq a where
>> (==) :: a -> a -> Bool
>>
>> -- | Equality comparisons which are equivalence relations.
>> -- It is laws-only and manual implementations would be
>> -- verified through property testing.
>> class PartialEq a => Eq a
>>
>> -- | Partial order
>> class PartialEq a => PartialOrd a where
>> compare' :: a -> a -> Maybe Ordering
>> (<) :: a -> a -> Bool
>> (<=) :: a -> a -> Bool
>> (>) :: a -> a -> Bool
>> (>=) :: a -> a -> Bool
>>
>> -- | Total order
>> class (PartialOrd a, Eq a) => Ord a where
>> compare :: a -> a -> Ordering
>> max :: a -> a -> a
>> min :: a -> a -> a
>>
>>
>> Cheers,
>> Hécate
>>
>> Le 25/10/2021 à 15:22, Joachim Breitner a écrit :
>> Hi,
>>
>> ah, yes, let me summarize my main motivation (perf benefits were just a
>> side-benefit I was hoping for):
>>
>> You can’t implement (/=) faster than (==) (up to, in the worst case,
>> the cost of a single `not`, which often gets optimized away anyways).
>>
>> As such, having (/=) in Eq was a (small) mistake back then, and it’s
>> worth fixing.
>>
>> There is one time cost of asking developers to _remove_ code. But code
>> that was probably not worth writing in the first place! And I don’t
>> blame them, the Eq class _invites_ writing that code.
>>
>> Then the benefits are twofold:
>>
>> * No more awkwards explanations about silly things in the likely first
>> type class that developers care about.
>>
>> * Less code to read, maintain, compile in all the libraries that _do_
>> define (/=) right now.
>>
>> * Devs who instantiate Eq in the future will not be tricked into
>> wondering if they need to implement (/=) and why.
>>
>> So even if “helps teaching beginners” doesn’t beat “having to bug
>> maintainers”, then maybe the second point (“saving all develpers time
>> and effort in the future”) does?
>>
>> Cheers,
>> Joachim
>>
>> --
>> Hécate ✨
>> 🐦: @TechnoEmpress
>> IRC: Hecate
>> WWW: https://glitchbra.in <https://glitchbra.in/>
>> RUN: BSD
>> Libraries mailing list
>> Libraries at haskell.org <mailto:Libraries at haskell.org>
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries <http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries>
> --
> Hécate ✨
> 🐦: @TechnoEmpress
> IRC: Hecate
> WWW: https://glitchbra.in <https://glitchbra.in/>
> RUN: BSD
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20211025/f4c774eb/attachment.html>
More information about the Libraries
mailing list