
Hi, I've posted a couple messages to the Haskell Cafe in the last few months. I'm new to Haskell. But, I've set out to implement my own vectors, matrices, complex numbers, etc. One goal I have, is to overload operators to work with my new types. The pursuit of this goal, has pushed me to learn a lot about the Haskell type system. When I get stuck from time-to-time, the kind folks on this list have pointed me in the right direction. I'm stuck now. One thing I want to avoid is adding new multiplication operators to handle multiplication of dissimilar types. For instance, I'd like to be able to have an expression like k * m where k is a Double and m is a Matrix. This doesn't work with the prelude's (*) operator because the prelude's (*) has signature: (*) :: (Num a) => a -> a -> a. To get around this, I wrote my own versions of a Multiply class that allows dissimilar types to be multiplied. You can see my Multiply class in the module at the end of this Email. At the bottom of the module, I've attempted to implement multiplication of the forms: scalar * matrix matrix * scalar matrix * matrix The problem is that when I try to do matrix * matrix at the interpreter, I get an error message from Glaskgow: *My_matrix> m1 * m2 <interactive>:1:3: Overlapping instances for Multiply (Matrix Double) (Matrix Double) (Matrix c) arising from use of `*' at <interactive>:1:3 Matching instances: My_matrix.hs:63:0: instance (Multiply a b c, Add c c c, Num a, Num b, Num c) => Multiply (Matrix a) (Matrix b) (Matrix c) My_matrix.hs:57:0: instance (Multiply a b c, Num a, Num b, Num c) => Multiply (Matrix a) b (Matrix c) My_matrix.hs:51:0: instance (Multiply a b c, Num a, Num b, Num c) => Multiply a (Matrix b) (Matrix c) In the definition of `it': it = m1 * m2 I don't understand how m1 * m2 can match the scalar multiplication instances. For instance, the scalar * matrix instance has signature: instance (Multiply a b c, Num a, Num b, Num c) => Multiply a (Matrix b) (Matrix c) where m1 in my expression would correspond to the 'a' type variable. But, 'a' is constrained to be a Num. However, I never made my Matrix type an instance of Num. Is there a work around for this? In my first implementation, I did not have the Num constraints in the matrix Multiply instances. I added the Num constraints specifically, to remove the ambiguity of the overlapping instance. Why didn't this work? Thanks, Jeff Harper
Begining of code for My_matrix.hs
{-# OPTIONS -fglasgow-exts #-} module My_matrix where import qualified Prelude as P import Prelude hiding ( (*), (+), (-), negate) default ( ) class Add a b c | a b -> c where (+) :: a -> b -> c class Multiply a b c | a b -> c where (*) :: a -> b -> c class Coerce a b where coerce :: a -> b infixl 7 * infixl 6 + instance Coerce Float Float where { coerce x = x } instance Coerce Float Double where { coerce x = realToFrac x } instance Coerce Double Double where { coerce x = x } instance Add Float Float Float where { (+) x y = ( x) P.+ ( y) } instance Add Float Double Double where { (+) x y = (coerce x) P.+ ( y) } instance Add Double Float Double where { (+) x y = ( x) P.+ (coerce y) } instance Add Double Double Double where { (+) x y = ( x) P.+ ( y) } instance Multiply Float Float Float where { (*) x y = ( x) P.* ( y) } instance Multiply Float Double Double where { (*) x y = (coerce x) P.* ( y) } instance Multiply Double Float Double where { (*) x y = ( x) P.* (coerce y) } instance Multiply Double Double Double where { (*) x y = ( x) P.* ( y) } -- Matrices are stored in a list of list. For now, I can create a -- matrix of Float, or Double. Later, I'd like to extend this and -- make it possible to create a matrix of other number types. For -- instance, it might be possible to have a matrix of complex or -- imaginary numbers. data Matrix a = Matrix [[a]] deriving Show -- For simplicity, the instances below omit the implementation for (*). -- This instance of Multiply is for doing multiplication of the form -- k * m where k is a scalar and m is a matrix. instance (Multiply a b c, Num a, Num b, Num c) => Multiply a (Matrix b) (Matrix c) where (*) x y = Matrix [[]] -- This instance of Multiply is for doing multiplication of the form -- m * k where k is a scalar and m is a matrix. instance (Multiply a b c, Num a, Num b, Num c) => Multiply (Matrix a) b (Matrix c) where (*) x y = Matrix [[]] -- This instance of Multiply is for doing multiplication of the form -- m1 * m2 where m1 and m2 are both matrices instance (Multiply a b c, Add c c c, Num a, Num b, Num c) => Multiply (Matrix a) (Matrix b) (Matrix c) where (*) x y = Matrix [[]] -- Some test variables to use in the interpreter k = (3.0::Double) m1 = Matrix [[1.0::Double]] m2 = Matrix [[2.0::Double]]