More type design questions

Konrad Hinsen hinsen@cnrs-orleans.fr
Mon, 18 Aug 2003 08:56:07 +0200


Continuing in my quest to understand type design in Haskell, here's anoth=
er=20
episode that leaves me scratching my head:

module Foo where

class Vect v a where
  (<+>) :: Floating a =3D> v a -> v a -> v a

data Vector a =3D Vector a a a

instance Vect Vector a where
  (<+>) (Vector x1 y1 z1) (Vector x2 y2 z2)
         =3D Vector (x1+x2) (y1+y2) (z1+z2)

instance Vect [Vector a] a where
  (<+>) l1 l2 =3D zipWith (<+>) l1 l2


The problem is the last instance declaration. Hugs says "Illegal type in =
class=20
constraint", which is not very explicit (which class constraint?). GHCI i=
s a=20
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 ca=
n't=20
remember where. Any help would be appreciated!

Konrad.