[Haskell-beginners] class and instance question
Walck, Scott
walck at lvc.edu
Thu May 20 06:35:34 EDT 2010
Hi folks,
I'm trying to make doubles and triples act like vectors, as in
(3,4) <+> (7,8) ==> (10,12)
(3,2,1) <+> (9,8,7) ==> (12,10,8)
6 *> (1,2,3) ==> (6,12,18)
I thought I should make a type class so that I could use <+> for both double addition and triple addition,
and *> for both double and triple scalar multiplication. (Some of this functionality is provided by
NumericPrelude, but I didn't need all of that, and I hoped this would be simple to write.)
The code below gives the error
NewVectorShort.hs:19:0:
Type synonym `Vector2D' should have 1 argument, but has been given 0
In the instance declaration for `BasicVector Vector2D'
Failed, modules loaded: none.
I don't understand how what I'm trying to do is different from, say, the Monad instance for Maybe.
(Maybe a) is a type, and (Vector2D a) is a type.
Thanks,
Scott
{-# LANGUAGE TypeSynonymInstances #-}
infixl 6 <+>
infixl 6 <->
infixl 7 *>
infixl 7 <*
class BasicVector v where
(<+>) :: v a -> v a -> v a
(<->) :: v a -> v a -> v a
(*>) :: Num a => a -> v a -> v a
(<*) :: Num a => v a -> a -> v a
v1 <-> v2 = v1 <+> fromInteger (-1) *> v2
v1 <* c = c *> v1
c *> v1 = v1 <* c
type Vector2D a = (a,a)
instance BasicVector Vector2D where
(ax,ay) <+> (bx,by) = (ax+bx,ay+by)
c *> (ax,ay) = (c*ax,c*ay)
More information about the Beginners
mailing list