Proposal: Remove Show and Eq superclasses of Num

Gábor Lehel illissius at gmail.com
Sat Sep 17 15:46:41 CEST 2011


On Fri, Sep 16, 2011 at 12:58 AM, Ian Lynagh <igloo at earth.li> wrote:
>
> Hi all,
>
> I would like to propose that we remove the Show and Eq superclasses from
> Num, i.e. change
>    class  (Eq a, Show a) => Num a  where
>        [...]
> to
>    class  Num a  where
>        [...]
>
>
> The first 2 attached patches (for base and ghc respectively) remove the
> Show constraint. I'm not aware of any justification for why this
> superclass makes sense.
>
>
> The next 2 patches (for base and unix respectively) remove the Eq
> constraint. Here's there's some justification in the superclass, as it
> makes
>    f 5 = ...
> work for any Num type, rather than also needing an Eq constraint, but
> personally I would be in favour of removing this superclass too.
> Noteworthy is that Bits now needs an Eq superclass for the default
> methods for 'testBit' and 'popCount'.
>
>
> The fifth patch (for base) is what prompted me to get around to sending
> this proposal. It lets us de-orphan the Show Integer instance.
>
>
> Any opinions?
>
>
> Suggested discussion deadline: 12th October
>
>
> Thanks
> Ian

As a thought experiment, with the ConstraintKinds extension coming up,
what would it take to make this change fully backwards compatible?

With ConstraintKinds, we could write:

type Num a = (Show a, Eq a, Num a) -- ???

...okay, maybe not.

We could define separate Nums in separate modules, though:

module OldNum where
import qualified NewNum
type Num a = (Show a, Eq a, NewNum.Num a)

and have the Num exported from the Prelude be the one from OldNum.
That way, code relying on a Num context also implying Show and Eq
doesn't break. But instance declarations break instead, which is
probably worse.

If we also have
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
more specifically, the "Multi-headed instance declarations" part from
the end, then writing

instance OldNum.Num Foo where
    (+) = ...
    ... etc. ...

would distribute the method definitions for OldNum.Num to Eq, Show,
and NewNum.Num. That gets us tantalizingly close. The problem is that
(a) instances for Num in existing code won't include definitions for
Eq and Show, and (b) separate instances for Eq and Show will be in
scope. The naive implementation of the feature will just emit
instances for Eq and Show with undefined method bodies, resulting
forthwith in a duplicate instance conflict.

One straightforward solution would be to refrain from emitting an
instance if (a) an instance for that class (for the given type) is
already in scope, and (b) the instance declaration for the
constraint-tuple doesn't include any definitions pertaining to that
class. Perhaps accompanied by a warning. I'm not sure if that's
palatable, though. It would mainly be problematic with classes for
which it's reasonable to declare instances with an empty body (maybe
because it's using the new Generics feature, for example): the user
might be expecting to declare a new instance and be surprised to find
that an existing one is being used instead, especially if the
'existing one' is introduced later, somewhere higher up the import
hierarchy. Warnings would at least let her know it's happening,
though.

Is there any other way to do it?

In any case, the question is whether a solution allowing full
backwards compatibility is possible and whether it has any likelihood
of being implemented in GHC in the near future. (Half of it is already
there, with ConstraintKinds.) If it's straight-up impossible or is
unlikely to be implemented, I see no reason not to +1 this proposal.
Otherwise, it might make sense to wait. If it's been more than a
decade, after all, what's another year?

-- 
Work is punishment for failing to procrastinate effectively.



More information about the Libraries mailing list