More type design questions

Bernard James POPE bjpop@cs.mu.OZ.AU
Mon, 18 Aug 2003 17:25:42 +1000 (EST)


> module Foo where
> 
> class Vect v a where
>   (<+>) :: Floating a => v a -> v a -> v a
> 
> data Vector a = Vector a a a
> 
> instance Vect Vector a where
>   (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2)
>          = Vector (x1+x2) (y1+y2) (z1+z2)
> 
> instance Vect [Vector a] a where
>   (<+>) l1 l2 = zipWith (<+>) l1 l2
>
> The problem is the last instance declaration. Hugs says "Illegal type in class 
> constraint", which is not very explicit (which class constraint?). GHCI is a 
> bit more verbose:
> 
>     Kind error: Expecting kind `* -> *', but `[Vector a]' has kind `*'
>     When checking kinds in `Vect [Vector a] a'
>     In the instance declaration for `Vect [Vector a] a'
> 
> I have vague memories of seeing mentioned the concept of "kind", but I can't 
> remember where. Any help would be appreciated!
> 
> Konrad.

Hi Konrad,

As you have mentioned Haskell's types have kinds, although they are almost
always hidden from view.

The kinds are there to help the compiler check whether types are well formed 
(including such things as instance declarations).

The syntax for kinds is very simple:

   kind = * | kind -> kind

The kind of all fully applied type constructors is *. Eg, the kind of Int,
Float, Double, 'Maybe a', [Char], [a], 'Either Bool ()', is *.

If a type constructor has arguments then its kind has an arrow (or more) in it.

The kind of 'Maybe' is *->* (read: the Maybe type constructor takes a (type) argument
of kind * and returns a type of kind *).

Notice in your type scheme for <+> that the "v" type is applied to the "a" type.
Because type "v" is applied to an argument (whose kind defaults to *), 
the kind of "v" is (*->*). Why does "a" have kind *, and not something else?
Well, that's for another discussion. All the gory details are in the Haskell 
report.  

So whatever type (constructor) you try to instantiate "v" with must also have 
this kind.

The type constructor Vector has this kind, so everything is fine there.

But the type [Vector a] has only kind * (because the list type constructor
is fully applied here).

One way around this might be to define a new type:

   newtype ListVector a = LV [Vector a]

   instance Vect ListVector a where
     (<+>) (LV l1) (LV l2) = LV $ zipWith (<+>) l1 l2

Though is is bit ugly to have to mention the LV constructor all the time.

Cheers,
Bernie.