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