Make Eq type class single method

Oleg Grenrus oleg.grenrus at iki.fi
Wed Oct 20 16:49:52 UTC 2021


The changes needed to compile GHC itself are small-ish, and indeed include
the primitive types and few others.

text library needs change as well, which is unfortunate

 import Prelude (Char, Bool(..), Int, Maybe(..), String,
-                Eq(..), Ord(..), Ordering(..), (++),
+                Eq(..), (/=), Ord(..), Ordering(..), (++),
                 Read(..),

It's somewhat common to import things explicitly from Prelude,
I do this often when writing something with wide base support,
and which uses the same names as in Prelude.
But this is simple change to do downstream.

I attach the patches for ghc, containers and text.
I encourage someone (Joachim?) to run the nofib suite.

Also, we coudl add builtin rewrite rules, rewriting not (eqInt8 x y)
to neInt8 x y if some benchmarks show that it would be beneficial.

- Oleg

On 20.10.2021 18.15, Viktor Dukhovni wrote:
> On Wed, Oct 20, 2021 at 04:39:21PM +0200, Joachim Breitner wrote:
>
>> I am revisiting some educational material about Haskell, and I stumble
>> over something that I keep stumbling over. I thought there was prior
>> discussion, but I couldn’t find it (operators hard hard to google for).
>>
>> Why does Eq have a (/=) method?
> For primitive types CPUs often have both '==' and '/=' instructions,
> and so a direct call to `(/=)` may be more efficient than calling
> `(not .) . (==)`.  The base package defines:
>
>     instance Eq Int8 where
>         (==) = eqInt8
>         (/=) = neInt8
>     instance Eq Int16 where
>         (==) = eqInt16
>         (/=) = neInt16
>     instance Eq Int32 where
>         (==) = eqInt32
>         (/=) = neInt32
>     instance Eq Int64 where
>         (==) = eqInt64
>         (/=) = neInt64
>
>     instance Eq Word8 where
>         (==) = eqWord8
>         (/=) = neWord8
>     instance Eq Word16 where
>         (==) = eqWord16
>         (/=) = neWord16
>     instance Eq Word32 where
>         (==) = eqWord32
>         (/=) = neWord32
>     instance Eq Word64 where
>         (==) = eqWord64
>         (/=) = neWord64
>
> There are also various cases involving equality/inequaility on
> getUnique, ...
>
>     compiler/GHC/Core/Coercion/Axiom.hs:instance Eq (CoAxiom br) where
>     compiler/GHC/Core/Coercion/Axiom.hs-    a == b = getUnique a == getUnique b
>     compiler/GHC/Core/Coercion/Axiom.hs-    a /= b = getUnique a /= getUnique b
>
>     compiler/GHC/Core/Class.hs:instance Eq Class where
>     compiler/GHC/Core/Class.hs-    c1 == c2 = classKey c1 == classKey c2
>     compiler/GHC/Core/Class.hs-    c1 /= c2 = classKey c1 /= classKey c2
>
> I don't know whether optimisations to use direct CPU instructions pay
> their way relative to the cost of larger Eq dictionaries in other
> contexts, but this seems to be at least a plausible reason.
>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: containers.diff
Type: text/x-patch
Size: 1037 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20211020/1d3a89f4/attachment.bin>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: text.diff
Type: text/x-patch
Size: 483 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20211020/1d3a89f4/attachment-0001.bin>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: ghc.diff
Type: text/x-patch
Size: 10719 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20211020/1d3a89f4/attachment-0002.bin>


More information about the Libraries mailing list