[Haskell-beginners] how to instance a class

Daniel Fischer daniel.is.fischer at web.de
Thu Feb 26 05:30:47 EST 2009


Am Donnerstag, 26. Februar 2009 09:12 schrieb Thomas Davie:
> On 26 Feb 2009, at 09:02, Daneel Yaitskov wrote:
> > --------------
> > But I can't instance my own class:
> >
> > class (Num a) => SVect a where
> > (***) :: Num b => a -> b -> a
> >
> > instance (Num t) => SVect (Vertex3 t) where
> > (Vertex3 x y z) *** c = Vertex3 (c*x) (c*y) (c*z)
> >
> > GHC posts about the error:
> >
> > surface.hs:107:36:
> >    Couldn't match expected type `b' against inferred type `t'
> >      `b' is a rigid type variable bound by
> >          the type signature for `***' at surface.hs:103:14
> >      `t' is a rigid type variable bound by
> >          the instance declaration at surface.hs:105:14
> >    In the second argument of `(*)', namely `x'
> >    In the first argument of `Vertex3', namely `(c * x)'
> >    In the expression: Vertex3 (c * x) (c * y) (c * z)
> > ------------------------
> >
> > I understand the "c" argument must have type as x,y and z, but
> > I don't know what need to do.

The problem is that the type signature of (***) promises that it works with 
*any* Num type, so if v :: Vertex3 Int and c :: Double, v *** c should work.
Or if v :: Vertex3 Double, c :: Complex Float, it should work, too.
It obviously can't work by simply multiplying every component of v with c.

But what you want isn't that general, what you want is that for every vector 
type a, there is some number type b, *depending on a*, for which (***) is 
defined.

The solution to the problem is
a) multiparameter typeclasses (MPTCs)
b) functional dependencies (FunDeps)
c) flexible instances

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances 
#-}

data Vec c = V !c !c
      deriving (Eq, Show)

instance (Num c) => Num (Vec c) where
    (V x y) + (V u v) = V (x+u) (y+v)
    (V x y) - (V u v) = V (x-u) (y-v)
	-- I omit the others for brevity


-- the SVec type class for a type a of vectors and a type b of scalars
-- the type of scalars is uniquely determined by the vector type,
-- that is what the "| a -> b" in the class declaration means
class (Num a, Num b) => SVec a b | a -> b where
    (***) :: a -> b -> a


-- since the type variable c appears twice in this instance declaration,
-- we need the FlexibleInstances extension
instance Num c => SVec (Vec c) c where
    (V x y) *** t = V (t*x) (t*y)

>
> I don't immediately see what is causing your error, but try
> downloading the VectorSpace package off hackage – it may save you a
> lot of wheel reinventing here.
>

That is probably a good idea. While it is instructive to roll your own, 
avoiding reinvention of wheels is a good thing (and you can compare your 
wheel with the other, too).

Cheers,
Daniel



More information about the Beginners mailing list