[Haskell-beginners] how to instance a class

Daneel Yaitskov rtfm.rtfm.rtfm at gmail.com
Thu Feb 26 03:02:39 EST 2009


Hi,


I study opengl and decided to improve the Vertex3 type.


data Vertex3 a => Vertex3 a! a! a!

a vertex and a vector are same. It is often need to multiple a vector
at a scalar or to calculate a scalar production of two vectors.

I have realized the Num class for the Vertex3 type:

instance (Num a) => Num (Vertex3 a) where
 (Vertex3 x y z) * (Vertex3 x' y' z')  = (Vertex3 (x*x') (y*y') (z*z'))
 (Vertex3 x y z) + (Vertex3 x' y' z')  = (Vertex3 (x+x')  (y+y') (z+z'))
 (Vertex3 x y z) - (Vertex3 x' y' z')  = (Vertex3 (x-x')  (y-y') (z-z'))
 abs (Vertex3 x y z) = (Vertex3 (abs x)  (abs y)  (abs z))
 signum (Vertex3 x y z) = (Vertex3 (signum x)  (signum y)  (signum z))
 negate (Vertex3 x y z) = (Vertex3 (-x) (-y) (-z))

instance (Fractional a) => Fractional (Vertex3 a) where 
 (Vertex3 x y z) / (Vertex3 x' y' z')  = (Vertex3 (x/x') (y/y') (z/z'))

--------------
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.


Daneel Yaitskov.



More information about the Beginners mailing list