Difference between revisions of "Context alias"

From HaskellWiki
Jump to navigation Jump to search
(Added section 'Equality constraints')
(Added hackaton roadmap)
(6 intermediate revisions by one other user not shown)
Line 6: Line 6:
   
 
The original proposal can be found on [http://repetae.net/recent/out/classalias.html a page on John Meachem’s website].
 
The original proposal can be found on [http://repetae.net/recent/out/classalias.html a page on John Meachem’s website].
  +
  +
==== Class aliases with new methods ====
  +
I would like to emphasize an important point from the original 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 called ''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 [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/monoids 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''. Because 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
  +
  +
-- Default implementations of existing methods:
  +
mempty = 0
  +
mappend = (+)
  +
  +
one = 1
  +
times = (*)
  +
  +
minus = (-)
  +
gnegate = negate
  +
  +
-- New methods with default implementations:
  +
(+) :: a -> a -> a
  +
(+) = mappend
  +
  +
(*) :: a -> a -> a
  +
(*) = times
  +
  +
(-) :: a -> a -> a
  +
(-) = minus
  +
  +
negate :: a -> a
  +
negate = gnegate
  +
  +
The question is: how is the above translated?
  +
  +
The new methods from ''Num'' should be placed in a new "internal" class: ''Num_NEW_METHODS'':
  +
  +
class Num_NEW_METHODS a where
  +
(+) :: a -> a -> a
  +
(*) :: a -> a -> a
  +
(-) :: a -> a -> a
  +
negate :: a -> a
  +
  +
What happens when a user defines an instance for ''Num''? Lets look at an example:
  +
  +
Say a user defines the natural numbers and makes them an instance of the ''Num'' class alias:
  +
  +
data N = Z | S N
  +
  +
instance Num N where
  +
Z + y = y
  +
S x + y = S (x + y)
  +
  +
Z * _ = Z
  +
S Z * y = y
  +
S x * y = y + x * y
  +
  +
x - Z = x
  +
S x - S y = x - y
  +
  +
fromInteger 0 = Z
  +
fromInteger (n+1) = S n -- You gotta love n+k patterns!
  +
  +
Note that the other methods of ''Num'' like ''mempty'', ''mappend'', ''one'' and ''times'' have default implementations in terms of the above.
  +
  +
First of all an instance for ''Num_NEW_METHODS'' will be defined:
  +
  +
instance Num_NEW_METHODS N where
  +
Z + y = y
  +
S x + y = S (x + y)
  +
  +
Z * _ = Z
  +
S Z * y = y
  +
S x * y = y + x * y
  +
  +
x - Z = x
  +
S x - S y = x - y
  +
  +
negate = gnegate
  +
  +
Then the other instances are defined using methods from ''Num_NEW_METHODS'':
  +
  +
instance Monoid N where
  +
mempty = 0
  +
mappend = (+)
  +
  +
instance Group N where
  +
minus = (-)
  +
  +
instance Multiplicative N where
  +
one = 1
  +
times = (*)
  +
  +
instance FromInteger N where
  +
fromInteger 0 = Z
  +
fromInteger (n+1) = S n -- You gotta love n+k patterns!
  +
  +
In conclusion, a class alias is a name for a context plus optionally a new class. The question is how useful this ability is.
  +
  +
The ''BoundedBelowJoinable'' could also be defined as a normal class with the necessary superclasses:
  +
  +
class (BoundedBelow a, SemiLatticeJoin a) => BoundedBelowJoinable a where
  +
joins :: [a] -> a
  +
joins xs = foldl join bottom xs
  +
  +
However, user now don't get a ''BoundedBelowJoinable'' for free when they have defined instances for ''BoundedBelow'' and ''SemiLatticeJoin''.
   
 
=== Improvements ===
 
=== Improvements ===
Line 14: Line 182:
   
 
context Foobar a = (Foo a, Bar a)
 
context Foobar a = (Foo a, Bar a)
  +
  +
However if we allow class "aliases" to be extended with new methods then a class "alias" is not just a name for a context. (It is actually a context with a new class)
  +
  +
Maybe we should keep the syntax really light like:
  +
  +
class Foobar a = (Foo a, Bar a)
   
 
==== Superclass constraints ====
 
==== Superclass constraints ====
Line 28: Line 202:
   
 
context Eq a => Num a = (Additive a, Multiplicative a)
 
context Eq a => Num a = (Additive a, Multiplicative a)
  +
  +
==== Functional dependencies ====
  +
  +
Does the following make sense?
  +
  +
class alias A a b = (B a b, C a b) | a -> b where ...
  +
  +
==== Associated data types and type synonyms ====
  +
  +
When <tt>{-# LANGUAGE TypeFamilies #-}</tt> is enabled, classes may declare [[GHC/Type_families|associated data types or associated type synonyms]].
  +
  +
If we allow class aliases to be extended with new methods, I think it make sense to also allow them to be extended with associated data types and type synonyms:
  +
  +
class A a = (B a, C a) where
  +
type T a
  +
data D a
   
 
==== Equality constraints ====
 
==== Equality constraints ====
Line 34: Line 224:
   
 
It makes sense to also allow them in class aliases (context aliases)
 
It makes sense to also allow them in class aliases (context aliases)
  +
 
 
==== Things to have in mind ====
 
==== Things to have in mind ====
   
Line 42: Line 232:
   
 
* <hask>Applicative</hask> should be a superclass of <hask>Monad</hask>
 
* <hask>Applicative</hask> should be a superclass of <hask>Monad</hask>
  +
   
 
== Implementation ==
 
== Implementation ==
   
 
Starting an implementation of context aliases is planned for the [[Hac5|5th Haskell Hackathon]].
 
Starting an implementation of context aliases is planned for the [[Hac5|5th Haskell Hackathon]].
  +
  +
Roadmap:
  +
# Context synonym declarations
  +
# Context synonym instances
  +
# New methods in 'context synonym'
  +
# Context synonym super classes/contexts

Revision as of 14:09, 17 April 2009

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 original 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 called 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. Because 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

     -- Default implementations of existing methods:
     mempty  = 0
     mappend = (+)
     one     = 1
     times   = (*)
     minus   = (-)
     gnegate = negate
     -- New methods with default implementations:
     (+) :: a -> a -> a
     (+) = mappend
     (*) :: a -> a -> a
     (*) = times
     (-) :: a -> a -> a
     (-) = minus
      
     negate :: a -> a
     negate = gnegate

The question is: how is the above translated?

The new methods from Num should be placed in a new "internal" class: Num_NEW_METHODS:

class Num_NEW_METHODS a where
    (+)    :: a -> a -> a
    (*)    :: a -> a -> a
    (-)    :: a -> a -> a
    negate :: a -> a

What happens when a user defines an instance for Num? Lets look at an example:

Say a user defines the natural numbers and makes them an instance of the Num class alias:

data N = Z | S N

instance Num N where
    Z   + y = y
    S x + y = S (x + y)
    Z   * _ = Z
    S Z * y = y
    S x * y = y + x * y
    x   - Z   = x
    S x - S y = x - y
    fromInteger 0     = Z
    fromInteger (n+1) = S n -- You gotta love n+k patterns!

Note that the other methods of Num like mempty, mappend, one and times have default implementations in terms of the above.

First of all an instance for Num_NEW_METHODS will be defined:

instance Num_NEW_METHODS N where
    Z   + y = y
    S x + y = S (x + y)
    Z   * _ = Z
    S Z * y = y
    S x * y = y + x * y
    x   - Z   = x
    S x - S y = x - y
    negate = gnegate

Then the other instances are defined using methods from Num_NEW_METHODS:

instance Monoid N where
    mempty  = 0
    mappend = (+)
instance Group N where
    minus = (-)
instance Multiplicative N where
    one   = 1
    times = (*)
instance FromInteger N where
    fromInteger 0     = Z
    fromInteger (n+1) = S n -- You gotta love n+k patterns!

In conclusion, a class alias is a name for a context plus optionally a new class. The question is how useful this ability is.

The BoundedBelowJoinable could also be defined as a normal class with the necessary superclasses:

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

However, user now don't get a BoundedBelowJoinable for free when they have defined instances for BoundedBelow and SemiLatticeJoin.

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)

However if we allow class "aliases" to be extended with new methods then a class "alias" is not just a name for a context. (It is actually a context with a new class)

Maybe we should keep the syntax really light like:

class 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)

Functional dependencies

Does the following make sense?

 class alias A a b = (B a b, C a b) | a -> b where ...

Associated data types and type synonyms

When {-# LANGUAGE TypeFamilies #-} is enabled, classes may declare associated data types or associated type synonyms.

If we allow class aliases to be extended with new methods, I think it make sense to also allow them to be extended with associated data types and type synonyms:

 class A a = (B a, C a) where
     type T a
     data D 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.

Roadmap:

  1. Context synonym declarations
  2. Context synonym instances
  3. New methods in 'context synonym'
  4. Context synonym super classes/contexts