[Haskell] PROPOSAL: class aliases

Ross Paterson ross at soi.city.ac.uk
Thu Oct 27 07:18:32 EDT 2005


On Thu, Oct 13, 2005 at 05:51:36AM -0700, John Meacham wrote:
> On Thu, Oct 13, 2005 at 12:21:41PM +0100, Simon Peyton-Jones wrote:
> > Anyway, my main point is: would a smaller change not suffice?
> 
> I do not think it suffices.
> 
> We could extend the supertyping relationship some more to make it
> suitable, but I think we will end up with the exact same proposal but
> with different terminology :)

For concreteness, here's a slight narrowing of Simon's version.
Given your H98 classes

	class Additive a where
		(+)     :: a -> a -> a
		zero    :: a

	class Additive a => Negative where
		(-)     :: a -> a -> a
		negate  :: a -> a

		x - y   = x + negate y
		negate x = zero - x

	class Multiplicative a where
		(*)     :: a -> a -> a
		one     :: a

extend the class syntax with an annotation on the assumptions (! for now),
to allow

	class (Show a, !Additive a, !Negative a, !Multiplicative a) =>
			Num a where
		fromInteger :: Integer -> a

		one     = fromInteger 1
		zero    = fromInteger 0

(This is for illustration -- I'm not claiming this is the ideal factoring
of the Num class.)

The ! annotations would be ignored during type inference.  Their only
meaning is

(a) the class declaration for Num may include defaults for the methods
    of the !'d superclasses,

(b) an instance declaration for Num also defines instances for the !'d
    superclasses, and thus may include definitions for the methods of Num
    and those superclasses.  Any methods of these classes not defined
    in the instance are assigned default definitions, with defaults in
    the Num class overriding any in the superclasses.

Thus if a Num instance is given, a Show instance must also be in scope
(as now), but Additive, Negative and Multiplicative instances cannot be
given, e.g.:

	instance Show Int65536 where
		showsPrec n = showsPrec n . toInteger

	instance Num Int65536 where
		(+) = primPlusInt65536
		(-) = primMinusInt65536
		(*) = primMultInt65536
		fromInteger = primFromInteger65536

In comparision with the class alias proposal, this loses aliasing, but
retains the ability to define defaults for superclasses, which is what
I've been missing for ages.

All these proposals need to address repeated inheritance, as in an
example from Davis Menendez:

	class (!Functor m) => Monad m where { fmap = liftM; ... }
	class (!Functor d) => Comonad d where { fmap = liftD; ... }

With the above rules, it would be illegal to define instances of both
these classes for the same type, but one could define

	class (!Monad f, !Comonad f) => MonadComonad f where
		...

as long as either the class includes a default definition of fmap,
or the instance includes a definition:

	instance MonadComonad Id where
		fmap f (Id x) = Id (f x)
		...

MPTCs raise extra issues, like

	class (!Functor f, !Functor g) => Something f g where
		fmap = ...

Which Functor is being given a default fmap?  I'd prefer to avoid this
by requiring that the !'d assumptions have exactly the same arguments
as the class being defined.



More information about the Haskell mailing list