This section documents GHC's implementation of multi-parameter type classes. There's lots of background in the paper Type classes: exploring the design space (Simon Peyton Jones, Mark Jones, Erik Meijer).
I'd like to thank people who reported shorcomings in the GHC 3.02 implementation. Our default decisions were all conservative ones, and the experience of these heroic pioneers has given useful concrete examples to support several generalisations. (These appear below as design choices not implemented in 3.02.)
I've discussed these notes with Mark Jones, and I believe that Hugs will migrate towards the same design choices as I outline here. Thanks to him, and to many others who have offered very useful feedback.
There are the following restrictions on the form of a qualified type:
forall tv1..tvn (c1, ...,cn) => type |
(Here, I write the "foralls" explicitly, although the Haskell source language omits them; in Haskell 1.4, all the free type variables of an explicit source-language type signature are universally quantified, except for the class type variables in a class declaration. However, in GHC, you can give the foralls if you want. See Section 6.7).
Each universally quantified type variable tvi must be mentioned (i.e. appear free) in type. The reason for this is that a value with a type that does not obey this restriction could not be used without introducing ambiguity. Here, for example, is an illegal type:
forall a. Eq a => Int |
Every constraint ci must mention at least one of the universally quantified type variables tvi. For example, this type is OK because C a b mentions the universally quantified type variable b:
forall a. C a b => burble |
forall a. Eq b => burble |
These restrictions apply to all types, whether declared in a type signature or inferred.
Unlike Haskell 1.4, constraints in types do not have to be of the form (class type-variables). Thus, these type signatures are perfectly OK
f :: Eq (m a) => [m a] -> [m a] g :: Eq [a] => ... |
This choice recovers principal types, a property that Haskell 1.4 does not have.
Multi-parameter type classes are permitted. For example:
class Collection c a where union :: c a -> c a -> c a ...etc. |
The class hierarchy must be acyclic. However, the definition of "acyclic" involves only the superclass relationships. For example, this is OK:
class C a where { op :: D b => a -> b -> b } class C a => D a where { ... } |
There are no restrictions on the context in a class declaration (which introduces superclasses), except that the class hierarchy must be acyclic. So these class declarations are OK:
class Functor (m k) => FiniteMap m k where ... class (Monad m, Monad (t m)) => Transform t m where lift :: m a -> (t m) a |
In the signature of a class operation, every constraint must mention at least one type variable that is not a class type variable. Thus:
class Collection c a where mapC :: Collection c b => (a->b) -> c a -> c b |
class C a where op :: Eq a => (a,b) -> (a,b) |
class Eq a => C a where op ::(a,b) -> (a,b) |
The type of each class operation must mention all of the class type variables. For example:
class Coll s a where empty :: s insert :: s -> a -> s |
class Coll s a where empty :: s a insert :: s a -> a -> s a |
class CollE s where empty :: s class CollE s => Coll s a where insert :: s -> a -> s |
Instance declarations may not overlap. The two instance declarations
instance context1 => C type1 where ... instance context2 => C type2 where ... |
EITHER type1 and type2 do not unify
OR type2 is a substitution instance of type1 (but not identical to type1)
OR vice versa
make it clear which instance decl to use (pick the most specific one that matches)
do not mention the contexts context1, context2 Reason: you can pick which instance decl "matches" based on the type.
There are no restrictions on the type in an instance head, except that at least one must not be a type variable. The instance "head" is the bit after the "=>" in an instance decl. For example, these are OK:
instance C Int a where ... instance D (Int, Int) where ... instance E [[a]] where ... |
instance Stateful (ST s) (MutVar s) where ... |
instance C a => C a where ... |
instance C a where op = ... -- Default |
class (C1 a, C2 a, C3 a) => C a where { } instance (C1 a, C2 a, C3 a) => C a where { } |
f :: C a => ... |
f :: (C1 a, C2 a, C3 a) => ... |
Unlike Haskell 1.4, instance heads may use type synonyms. As always, using a type synonym is just shorthand for writing the RHS of the type synonym definition. For example:
type Point = (Int,Int) instance C Point where ... instance C [Point] where ... |
instance C (Int,Int) where ... |
type P a = [[a]] instance Monad P where ... |
The types in an instance-declaration context must all be type variables. Thus
instance C a b => Eq (a,b) where ... |
instance C Int b => Foo b where ... |