More type design questions

Brandon Michael Moore brandon@its.caltech.edu
Mon, 18 Aug 2003 10:26:25 -0700 (PDT)


I think what you want are functional dependencies.

On Mon, 18 Aug 2003, Konrad Hinsen wrote:

> On Monday 18 August 2003 09:25, Bernard James POPE wrote:
>
> > 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:
> ...
>
> Thanks for the explanation! It seems that what I need (but what apparently
> doesn't exist) is the equivalent of a lambda expression for type
> constructors, then I could write something like
>
> instance Vect (\a -> [Vector a]) a where
> ...
>
> > 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.
>
> It's not just ugly, it destroys the generality of my code. I would like to be
> able to have generic list processing functions (think of "map") produce lists
> of vectors and then be able to apply the functions in class "Vect" to them.
> If I introduce a new type, then I will have to put wrapper functions in many
> places. I really want a type that is a list *and* an instance of class Vect.
>
> In fact, what I'd really like to have is even more general:
>
> instance Vect v a => Vect [Vect v a] where
> ...
>
> i.e. defining that a list of any Vect instance is itself a Vect instance. But
> I could live with the case that I presented initially.
>
> Konrad.

The class you had,

class (Num a) =>  Vector v a where
  <+> :: v a -> v a -> v a
  <*> :: a -> va -> v a

requires that v be a type constructor that gives vectors when applied to a
ring. Using functional dependencies you can write a types class that says
a type is a vector containing elements of type a:

class (Num a) => Vector v a | v -> a where
  <+> :: v -> v -> v
  <*> :: a -> v -> v

The type of <+> wouldn't be allowed without the dependancy v -> a, becuase
a is never mentioned in the type so there would be no way to figure out
what instance to use. The dependancy says "knowing the v type of an
instance uniquely determines the a type". The compiler checks that your
instance declarations satisfy this, and use the information when resolving
overloading.

you can still declare an instance for your vector type

instance (Num a) => Vector (Vector a) a where
  <+> = ...
  <*> = ...

(Notice that this declare an instance for all a)

You can also declare instances for v that are not type constructors

data Point = Point Float Float Float

instance Vector Point Float where
  (Point x y z) <+> (Point x2 y2 z2) = Point (x+x2) (y+y2) (z+z2)
  a <*> (Point x y z) = Point (a*x) (a*y) (a*z)

And, you can declare an instance for lists:

instance (Vector v a) => Vector [v] a where
  as <+> bs = zipWith (<+>) as bs
  a <*> vs = map (a<*>) vs

With GHC this requires -fglasgow-exts (and maybe -fundecidable-instances),
with Hugs you need +98.

The GHC users guide, the Haskell Wiki, and the paper "Type Classes:
Exploring the Design Space" are all good places for more information.

Brandon