[Haskell-cafe] Context for type parameters of type constructors

Henning Thielemann iakd0 at clusterf.urz.uni-halle.de
Mon Apr 5 14:59:18 EDT 2004


On 3 Apr 2004, Dylan Thurston wrote:

> You might want to add a functional dependency, if you only have one
> type of scalars per vertor space:
> 
> > class VectorSpace v a | v -> awhere
> >    zero  :: v
> >    add   :: v -> v -> v
> >    scale :: a -> v -> v
> 
> But then again, you might not.
> 
> > > instance Num a => VectorSpace a a where
> > >    zero  = 0
> > >    add   = (+)
> > >    scale = (*)

I see ... functional dependency means "for each 'v' there is only one 'a'
that forms a VectorSpace with 'v'". Thus the "VectorSpace a a" instance
would exclude any other instance.

Since this instance causes 'undecidable instance' and 'overlapping
instance' errors in each constellation I tried I finally decided to
content myself with special instances

 instance VectorSpace Double Double
 instance VectorSpace Float  Float

 These will be the anchors for each type construction recursion needed for
more complex VectorSpaces.  But e.g. 
  instance VectorSpace (Complex Double) (Complex Double)
 is still rejected as overlapping with
  instance (RealFloat v, VectorSpace a v) => VectorSpace a (Complex v)
 of course ... unfortunately.

 In addition I separated a class VectorSpacePure from the VectorSpace
class that contains the operations that don't need the scalar type 'a',
i.e.  'zero' and 'add'. Further I swapped consistently 'a' and 'v' in the
class definition and in the quantity data type, i.e. "class VectorSpace a
v" and "data Quantity a v". I suppose that it will more oftenly be
necessary to say something about the vectors that can built from a certain
scalar (i.e. Quantity a) rather than about the scalar types that can be
the base of a vector type. 

> By the way, depending how you resolve the issue above, you might want
> instead
> 
> > instance (RealFloat a, VectorSpace b a) => VectorSpace [b] a where
> > ...

That's really a nice generalization! With the specialised instances for
Float and Double as shown above this works. Now I can built VectorSpace
over several levels, e.g. a list of complex numbers as vectors with
respect to real numbers. But it prohibits functional dependency, right? 
Functional dependency would probably allow the compiler to detect which
scalar type is associated with an vector and thus the compiler wouldn't
ask me to tell it explicitly all the time. 

> Alternatively, if you want to consider varying the scalars, you can
> add 'a' as a dummy type variable to 'Quantity':
> 
> > data Quantity v a = Quantity v
> >
> > instance (Show v, Fractional a, Normed v a) =>
> >         Show (Quantity v a) where
> >    show (Quantity v) =
> >        let nv::a = norm v
> >        in  (show (scale (1/nv) v)) ++ "*" ++
> >            (show nv)

Since I can't use functional dependency I chose this way. 

Maybe a type class like the VectorSpace finds the way to a revised version
of Prelude?


Thanks a lot for the help!




More information about the Haskell-Cafe mailing list