Context alias

From HaskellWiki
Revision as of 09:54, 16 April 2009 by Basvandijk (talk | contribs)
Jump to navigation Jump to search

Context aliases, also known as class aliases, are a long-requested feature of Haskell. This feature would allow class hierarchies to be restructured without breaking compatibility to a certain degree. Also, it would make fine-grained class hierarchies usable.

The proposal

The original class alias proposal

The original proposal can be found on a page on John Meachem’s website.

Class aliases with new methods

I would like to emphasize an important point from the proposal that was not emphasized enough:

Lets look at one of the examples from the original proposal:

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

Notice that BoundedBelowJoinable doesn't have the alias keyword. Is this a syntax error or is it allowed? It is allowed because BoundedBelowJoinable is not just an alias for (BoundedBelow a, SemiLatticeJoin a). It also declares a new method: joins.

So why is this usefull?

Users can declare instances for BoundedBelow and SemiLatticeJoin and get joins for free or they can declare an instance for BoundedBelowJoinable and define an optimized joins for their type.

Lets look at another example why this ability, to give a class alias new methods, is useful. Again I take an example from the original proposal but I slightly change it:

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

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

Ideally we would want to split it up using classes from the monoids package:

 class Monoid a where
     mempty  :: a
     mappend :: a -> a -> a
   
 class Monoid a => Group a where
     gnegate   :: a -> a
     minus     :: a -> a -> a
     gsubtract :: a -> a -> a
     gnegate         = minus mempty
     a `minus` b     = a `mappend` gnegate b 
     a `gsubtract` b = gnegate a `mappend` b
 class Multiplicative a where
     one   :: a
     times :: a -> a -> a
 class FromInteger a where
     fromInteger :: Integer -> a

But this creates some problems as mentioned in the proposal:

  • People using the new prelude have to write the ungainly (Monoid a, Group a, Multiplicative a, FromInteger 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 of the proposal about alternate preludes in general.

We can solve all of them by creating a class alias:

 class alias Num a = (Monoid a, Group a, Multiplicative a, FromInteger a)

Or can we? Unfortunately this Num is different than the original Num. Instead of the methods (+), (-), (*) and negate we have mappend, minus, times and gnegate.

Fortunately we can add the original names as new methods to the class alias and give them default definitions in terms of the new names:

 class Num a = (Monoid a, Group a, Multiplicative a, FromInteger a) where
     mempty  = fromInteger 0
     mappend = (+)
     one     = fromInteger 1
     times   = (*)
     minus   = (-)
     gnegate = negate
     (+) :: a -> a -> a
     (+) = mappend
     (*) :: a -> a -> a
     (*) = times
     (-) :: a -> a -> a
     (-) = minus
      
     negate :: a -> a
     negate = gnegate

Improvements

“Context alias” instead of “class alias”

A “class alias” actually doesn’t stand for a class but for a context (or a part of a context). So it might be better to choose a slightly different syntax:

context Foobar a = (Foo a, Bar a)

Superclass constraints

John Meacham proposes the following syntax for class aliases (context aliases) with superclass constraints:

class alias Num a = Eq a => (Additive a, Multiplicative a)

This is not consistent with the superclass syntax of class declarations. I think, we should use this syntax:

class alias Eq a => Num a = (Additive a, Multiplicative a)

Or better:

context Eq a => Num a = (Additive a, Multiplicative a)

Equality constraints

When {-# LANGUAGE TypeFamilies #-} is enabled, type contexts can include equality constraints (t1 ~ t2).

It makes sense to also allow them in class aliases (context aliases)

Things to have in mind

In order to get the context alias extension well, we should have an eye on problems we might want to solve with the help of context aliases. Here are some:

  • MonadPlus should just be a combination of Alternative and Monad (actually, Alternative f should just be a combination of Applicative f and forall a. Monoid (f a))
  • Applicative should be a superclass of Monad

Implementation

Starting an implementation of context aliases is planned for the 5th Haskell Hackathon.