[Haskell] PROPOSAL: class aliases

John Meacham john at repetae.net
Wed Oct 12 20:00:40 EDT 2005


= Class Aliases =

This is a proposal for a language extension which will hopefully mitigate the
issues holding back evolution of the standard prelude as well as provide
useful class abstraction capabilities in general.

It's main goals are to

* remove the false tension between the granularity of a class hierarchy and
  its practical usability.

* Allow one to modify a class hierarchy while retaining 100% backwards
  compatibility with a class API. with a specific use being able to replace
  the prelude's numeric hierarchy while retaining full haskell 98 compatibility,
  including the fact that libraries that only know about haskell 98 will have
  their instances automatically propagated to the new class hierarchy (and
  vice versa), so switching over can be fully incremental.

* allow one to provide simple and advanced interfaces to a class hierarchy,
  much as one can do with function libraries.

* it incidentally allows certain things that have been requested on the list
  as 'nice to have' but not world shattering.

* not interfere with separate compilation and be describable by a
  straightforward source->source translation.

feel free to skip the next section if you know the issues involved in
replacing the numeric hierarchy of the prelude transparently :) This
specification is meant to be informal but precise and complete. if any
of the translation rules are unclear, then let me know.

== The Problem ==

Many alternate preludes have been proposed, however to date none have gained
popularity beyond the extensions to the standard libraries provided by
fptools. Since as a general rule, the haskell community only likes to
standardize changes that have been actively used and implemented already (a
very good policy) this makes evolution of the standard problematic.

Although it is easy enough to provide new functions and datatypes, providing
wrapper routines with the old interfaces to allow incremental use of a new
prelude or any library. there is no way to hide the fact that you changed a
class hierarchy. if you split a class into two, every instance has to change,
even if the split is irrelevant to a given datatype. Furthermore, depending
on how you split or join classes, many type signatures will have to be
rewritten. Since Haskell projects tend to be amalgamations of many different
libraries and code from previous projects, this makes using alternate
preludes with anything larger than a toy project unpossible.

The problem is compounded when you consider the fact that we ideally want
multiple competing preludes or certainly different versions of the same one.
Imagine a library that provides a handy new Numeric datatype. the writer of
the library only knows about the main prelude and doesn't concern himself with
the various experimental preludes out there so declares an instance for Num.
Bill comes along and realizes he needs an instance for the new Prelude so
declares it an instance of ExperimentalNum, Phil, who also uses the library
and the new experimental prelude needs to declare his own ExperimentalNum
instance. suddenly Bill's and Phil's libraries cannot be combined by Susan who
just wants to get work done and needs both Bill's and Phil's libraries.

The basic issue is that you end up with a quadratic number of instances for
every datatype combined with every alternative prelude and it is not clear who
should be providing these instances. every library writer should not need to
know about every alternate prelude out there and vice versa. Not only that
but most of the instances will be very redundant, ExperimentalNum and Num
most likely provide many of the same operations, you should only need to
declare an instance for one and have it automatically propegated to the other.


== The Extension ==

In haskell, you may create abstract data types, where you are free to change
the internal representation without affecting the visible interface, you may
create function impedance matching libraries, providing alternate interfaces
to the same functionality. however, there is no way to abstract your class
hiearchy. there is no way to hide your class layout in such a way you can
change it behind the scenes, once a sizable codebase is built up expecting a
certain class layout, there is no incremental migration path to something better.

This extension allows the creation of class aliases, or effectively different
views of the class hierarchy. this allows library writers to change the class
hierarchy under the hood without affecting the visible interface as well as
providing cleaner interfaces to begin with, hiding unimportant implementation
details of how the classes are laid out from regular users, while providing
the more advanced interfaces to power users.

This extension may be carried out completely in the front end via a
source->source translation and does not inhibit separate compilation.

given

>  class Foo a where
>    foo :: a -> Bool
>    foo x = False
>
>  class Bar b where
>    bar :: Int -> b -> [b]

We allow new constructs of this form (the exact syntax is flexible of course):


>  class alias (Foo a, Bar a) => FooBar a where
>    foo = ...

what this does is declare 'FooBar a' as an alias for the two constraints 'Foo a'
and 'Bar a'. This affects two things.

FooBar a may appear anywhere a class constraint may appear otherwise, it's
meaning is simply (Foo a, Bar a) and the expansion may be carried out as a
simple macro replacement, like type synonyms.

The other thing is that one may declare instances of FooBar.

> instance FooBar Int where
>    foo x = x > 0
>    bar n x = replicate n x

this expands to:

> instance Foo Int where
>    foo x = x > 0
>
> instance Bar Int where
>    bar n x = replicate n x


The meaning of declaring a type an instance of a class alias is that it
declares the type an instance of each class that makes up the alias,
distributing the method definitions to their respective classes, using the
default methods declared in the class alias if available, otherwise using the
default methods of the underlying class. This also may be carried out as a
simple translation in the front end.

let us look at a more concrete example:

the current Num class in the Prelude is (more or less) this

> class Num a where
>     (+), (*)    :: a -> a -> a
>     (-)         :: a -> a -> a
>     negate      :: a -> a
>     fromInteger :: Integer -> a

ideally we would want to split it up like so (but with more mathematically
precise names):

> class Additive a where
>   (+) :: a -> a -> a
>   zero :: a
>
> class Additive a => AdditiveNegation where
>     (-)         :: a -> a -> a
>     negate      :: a -> a
>     x - y  = x + negate y
>
> class Multiplicative a where
>   (*) :: a -> a -> a
>   one :: a
>
> class FromInteger a where
>     fromInteger      :: Integer -> a



now this presents some problems:

* people using the new prelude have to write the ungainly (FromInteger a,
AdditiveNegation a, Multiplicative a) and declare separate instances for all of them.

* if at some point a HasZero class is separated out then everyone needs to
modify their instance declarations.

* Num still must be declared if you want it to work with old prelude
  functions, containing completely redundant information.

* all the problems mentioned in the second section above about alternate
  preludes in general.


these can be solved with the changing of Num into a class alias.

> class alias (Addititive a, AdditiveNegation a,
>              Multiplicative a, FromInteger a) => Num a where
>    one = fromInteger 1
>    zero = fromInteger 0
>    negate x = zero - x


now, all of the above problems are solved. You may use the short 'Num a'
notation for numbers, if a HasZero class is split out then it doesn't matter
because declaring something a (Num a) will propagate your methods to it
properly. declaration of an instance for Num will automatically create
instances for all the other classes, declaring separate instances for each of
the other classes will give you the equivalent of an instance for Num. people
writing libraries need not concern themselves with the alternate prelude or
the haskell 98 one, they can pretend the other doesn't exist and their
instance declarations will automatically create appropriate instances in the
alternate prelude.


== Another Example ==

This example is unrelated to creating an alternate prelude but shows how this
extension is a useful abstraction tool in general.

imagine we want to create a great lattice class library. I mean, a super
really flexible one.

> class Lattice a where
>         meet :: a -> a -> a
>         join :: a -> a -> a

of course, you want to be able to express lattices with a distinguished top
and bottom.

> class Lattice a => BoundedLattice a where
>         top :: a
>         bottom :: a
>         meets :: [a] -> a
>         joins :: [a] -> a
>         meets xs = foldl meet top xs
>         joins xs = foldl join bottom xs

hmm.. but then you realize you might want semi lattices.. so you change it too

> class SemiLatticeMeet a where
>         meet :: a -> a -> a
>
> class SemiLatticeJoin a where
>         join :: a -> a -> a
>
>
> class (SemiLatticeMeet a,SemiLatticeJoin a) => BoundedLattice a where
>         top :: a
>         bottom :: a
>         meets :: [a] -> a
>         joins :: [a] -> a
>         meets xs = foldl meet top xs
>         joins xs = foldl join bottom xs

but then you realize you might want bounded semilattices so you come up with
the following. your final super flexible lattice class.

> class BoundedAbove a where
>         top :: a
>
> class BoundedBelow a where
>         bottom :: a
>
> class SemiLatticeMeet a where
>         meet :: a -> a -> a
>
> class SemiLatticeJoin a where
>         join :: a -> a -> a
>
>
> meets :: (BoundedAbove a,SemiLatticeMeet a) => [a] -> a
> meets xs = foldl meet top xs
>
> joins :: (BoundedBelow a,SemiLatticeJoin a) => [a] -> a
> joins xs = foldl join bottom xs



notice two things beyond the points mentioned above:

1. You have pissed off all your users... they just wanted to declare a simple
bounded lattice and now they have to type a whole lot of crud to do so. refer
to the docs several times to see how you named things and know some
non-trivial things about lattices.

2. creating a simple bounded lattice instance for Bool requires writing 4
instances, none of which actually say 'BoundedLattice'! not very intuitive or
flexible.

3. you can no longer make  meets and joins members of a type class, meaning
you cannot create optimized versions of them for certain types which most
definitely exist and are important for many applications of lattices. you have
traded flexibility in one direction for flexibility in another.

of course, you could do something like

> class (BoundedBelow a, SemiLatticeJoin a) => BoundedBelowJoinable a where
>         joins :: [a] -> a

but things are already getting absurd. no user is going to type
BoundedBelowJoinable constantly when they just want a lattice. there is a
fundamental weakness in haskell here in that it creates a false tension
between these two types of flexibility, this is compounded by the inability to
change type classes without changing your interface so it is hard to tweak
things if it turns out you chose something non-ideally.

now, lets look at the above with class aliases.


> class SemiLatticeMeet a where
>         meet :: a -> a -> a
>
> class SemiLatticeJoin a where
>         join :: a -> a -> a
>
> class alias (SemiLatticeMeet a, SemiLatticeJoin a) => Lattice a
>
> class BoundedAbove a where
>         top :: a
>
> class BoundedBelow a where
>         bottom :: a
>
> class alias (BoundedAbove a, BoundedBelow a) => Bounded a
>
>
> class (BoundedBelow a, SemiLatticeJoin a) => BoundedBelowJoinable a where
>         joins :: [a] -> a
>         joins xs = foldl join bottom xs
>
> class (BoundedAbove a, SemiLatticeMeet a) => BoundedAboveMeetable a where
>         meets :: [a] -> a
>         meets xs = foldl meet top xs
>
> class alias (BoundedBelow a, BoundedAbove a, SemiLatticeMeet a,
>              SemiLatticeJoin a,BoundedBelowJoinable a,
>              BoundedAboveJoinable b) => BoundedLattice a

this looks complicated but you really wanted to write a super-ultra fancy
lattice class. But from a library users point of view it is great:

The library user simply need to declare

> instance BoundedLattice Bool where
>         top = True
>         bottom = False
>         meet = (&&)
>         join = (||)

and _all_ of the above classes are filled in properly.

someone else can write

> instance Lattice Integer where
>         join = max
>         meet = min

while a power user is free to declare his SemiLattices or BoundedAboveMeetables or
whatever.

this is a great benefit IMHO. There has always been a false tension between
the granularity of your class hierarchy and its practical usability. this
extension gets rid of that tension.


== Notes ==

* class aliases are also able to introduce new superclass constraints, such as
  in the Num example we also want to enforce a (Eq a, Show a) superclass
  constraint. the interpretation is straightforward, Num in type signatures
  expands as if those were part of the alias and when declaring instances the
  existence of instances for the superclasses are checked, but not filled in
  automatically. I didn't show an example so as to not confuse the basic idea
  and because I have not come up with a syntax I am happy with. (suggestions
  welcome)

* How these interact with other type class extensions would have to
  be figured out. it shouldn't present an issue and I think even if class
  aliases needed to be restricted to single parameter type classes (unlikely)
  then they would still be useful.

* deciding what to display in error messages is an issue. but no more
  complicated than deciding whether to show a type synonym or an underlying
  type. a heuristic like show the most general constraint that can be
  expressed with the names in scope should suffice.

* although it is basically a source->source translation, in practice it could
  not be carried out by a preprocessor because all the names needed would not
  be in scope and we would want to propagate the class alias information in
  the 'hi' files (or equivalent) of the compiler.

* I had an earlier supertyping proposal you might know about, I feel this is
  a much better proposal even though it doesn't fully subsume my supertyping
  proposal, I feel it solves the problems it was meant to solve in a cleaner
  and easier to implement way.

* You may wonder why for the num example I put Additive a in the class alias
  even though it was already a superclass of AdditiveNegation. that is
  because class aliases do not change the meaning of superclasses, you need
  to explicitly list a class if you want instance declarations to propagate
  methods to it. superclasses are checked just like normal in class aliases.

* incidental but not earth-shattering benefits include being able to
  declare an instance for a class and all its superclasses at once,
  smarter defaults when you are combining related classes, and much
  nicer type signatures by being able to create your own aliases for
  common combinations of classes.

-- 
John Meacham - ⑆repetae.net⑆john⑈ 


More information about the Haskell mailing list