Problems defining a type with a multiplication function

I'm trying to define a Quaternion, which is sort of a four-element vector with special rules for multiplication. ----- Quaternion.hs ----- data Quaternion = Quaternion Double Double Double Double deriving (Show) (*) :: (Quaternion a) => a -> a -> a (*) (Quaternion w1 x1 y1 z1) (Quaternion w2 x2 y2 z2) = Quaternion w x y z where w = w1*w2 - x1*x2 - y1*y2 - z1*z2 x = x1*w2 + w1*x2 + y1*z2 - z1*y2 y = w1*y2 - x1*z2 + y1*w2 + z1*x2 z = w1*z2 + x1*y2 - y1*x2 + z1*w2 ----- end code ----- When I try to load this into ghci, I get: Quaternion.hs:6:13: Ambiguous occurrence `*' It could refer to either `Main.*', defined at Quaternion.hs:5:0 or `Prelude.*', imported from Prelude ... and lots more messages like that. I understand roughly what the message means, but I don't know how to tell it that when I use "*" within the definition, I just want ordinary multiplication. Thanks in advance for any help! Amy

Amy,
Quaternion.hs:6:13: Ambiguous occurrence `*' It could refer to either `Main.*', defined at Quaternion.hs:5:0 or `Prelude.*', imported from Prelude
... and lots more messages like that. I understand roughly what the message means, but I don't know how to tell it that when I use "*" within the definition, I just want ordinary multiplication. Thanks in advance for any
You're redefining (*) in Main, which creates the ambiguity, which is the problem. One alternative is, instead of creating a new ambiguous (*), is use the existing one, and make it apply to your type. The existing (*) belongs to the typeclass Num. You can make your type an instance of Num, with your definition of (*): instance Num (Quaternion a) where q1 * q2 = ... q1 + q2 = undefined -- or, better, a valid definition q1 - q2 = undefined ... You'll find that this cascades into requiring you to define a handful of other class functions (+, -, negate, abs, signum, fromInteger) and you'll need Eq and Show instances. You can derive the latter, and you can give trivial (undefined or error) definitions for, say, negate if you won't be using it. Hope this helps. John

You need to write an instance of the Num class, eg instance Num Quaternion where (Q a b c d) + (Q e f g h) = ... (Q a b c d) * (Q e f g h) = ... etc This allows Haskell to overload things like numbers. You seem to be headed in the right direction w/ your type signature, except (*) has type Num a => a -> a -> a Which means "For any type `a` that is an instance of the type class `Num`, this is a closed binary function on that type" HTH /Joe On Sep 9, 2009, at 4:51 PM, Amy de Buitléir wrote:
I'm trying to define a Quaternion, which is sort of a four-element vector with special rules for multiplication.
----- Quaternion.hs ----- data Quaternion = Quaternion Double Double Double Double deriving (Show)
(*) :: (Quaternion a) => a -> a -> a (*) (Quaternion w1 x1 y1 z1) (Quaternion w2 x2 y2 z2) = Quaternion w x y z where w = w1*w2 - x1*x2 - y1*y2 - z1*z2 x = x1*w2 + w1*x2 + y1*z2 - z1*y2 y = w1*y2 - x1*z2 + y1*w2 + z1*x2 z = w1*z2 + x1*y2 - y1*x2 + z1*w2
----- end code -----
When I try to load this into ghci, I get:
Quaternion.hs:6:13: Ambiguous occurrence `*' It could refer to either `Main.*', defined at Quaternion.hs:5:0 or `Prelude.*', imported from Prelude
... and lots more messages like that. I understand roughly what the message means, but I don't know how to tell it that when I use "*" within the definition, I just want ordinary multiplication. Thanks in advance for any help!
Amy
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Amy,
instance Num Quaternion where
Use this (from Joe's email), and not
instance Num (Quaternion a)
this (from mine). I had skimmed your code too quickly and wrote the above in error because I'd thought you had make Quaternion parametric. Unless you want the parametricity, as in: data Quaternion a = Quaternion a a a a class (Num a) => Num (Quaternion a) where ... Cheers, John

On Wed, Sep 09, 2009 at 09:51:34PM +0100, Amy de Buitléir wrote:
----- Quaternion.hs ----- data Quaternion = Quaternion Double Double Double Double deriving (Show)
(*) :: (Quaternion a) => a -> a -> a
Also, I should point out that the '(blah) => ...' syntax is only for type *classes*; Quaternion is just a data type so it doesn't make sense to use it in this way. The type signature instead ought to just say (*) :: Quaternion -> Quaternion -> Quaternion although as others have pointed out you will still get the error about (*) being ambiguous. You can either implement Num as others have suggested, or just use a different name for quaternion multiplication, such as, say, (*!). -Brent
participants (4)
-
Amy de Buitléir
-
Brent Yorgey
-
Joe Fredette
-
John Dorsey