
I made a very simple matrix module that implements matrix sum and multiplication. It does not require any especific type since it uses Num [[a]]. So instead of typing something like Matrix [[1,0],[0,2]] * Matrix [[1,2],[3,4]] you can just type [[1,0],[0,2]]*[[1,2],[3,4]] It needs -fglasgow-exts Atila module SimpleMatrix where instance Num a => Num [[a]] where fromInteger x = [[fromInteger x]] abs x = map (map abs) x (+) [ ] y = y (+) x [ ] = x (+) x y = zipWith (zipWith (+)) x y (*) x y = map (matrixXvector x) y where -- matrixXvector :: Num a => [[a]] -> [a] -> [[a]] matrixXvector m v = foldl vectorsum [] $ zipWith vectorXnumber m v -- vectorXnumber :: Num a => [a] -> a -> [a] vectorXnumber v n = map (n*) v -- vectorsum :: [a] -> [a] -> [a] vectorsum [] y = y vectorsum x [] = x vectorsum x y = zipWith (+) x y _______________________________________________________ Novidade no Yahoo! Mail: receba alertas de novas mensagens no seu celular. Registre seu aparelho agora! http://br.mobile.yahoo.com/mailalertas/

fromInteger x = [[fromInteger x]]
Wouldn't you want the expression [[1,0],[0,2]] + 10 to yield [[11,10],[10,12]] instead of [[11]] ? I guess you would need some complicated machinery so this is one thing you have to ignore to keep your otherwise nifty instance nice and simple. Jared. -- http://www.updike.org/~jared/ reverse ")-:"
abs x = map (map abs) x (+) [ ] y = y (+) x [ ] = x (+) x y = zipWith (zipWith (+)) x y (*) x y = map (matrixXvector x) y where -- matrixXvector :: Num a => [[a]] -> [a] -> [[a]] matrixXvector m v = foldl vectorsum [] $ zipWith vectorXnumber m v -- vectorXnumber :: Num a => [a] -> a -> [a] vectorXnumber v n = map (n*) v -- vectorsum :: [a] -> [a] -> [a] vectorsum [] y = y vectorsum x [] = x vectorsum x y = zipWith (+) x y
_______________________________________________________ Novidade no Yahoo! Mail: receba alertas de novas mensagens no seu celular. Registre seu aparelho agora! http://br.mobile.yahoo.com/mailalertas/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Good point. And there is another problem: one could expect 10 * [[1,2],[3,4]] to be equal to [[10,20],[30,40]] and in this case 10 should be equal to [[10,0],[0,10]], instead of [[10,10],[10,10]] or [[10]]. I dont see how to fix this. Could be better to forget about fromInteger... Atila Jared Updike wrote:
fromInteger x = [[fromInteger x]]
Wouldn't you want the expression
[[1,0],[0,2]] + 10
to yield
[[11,10],[10,12]]
instead of [[11]] ? I guess you would need some complicated machinery so this is one thing you have to ignore to keep your otherwise nifty instance nice and simple.
Jared.
_______________________________________________________ Novidade no Yahoo! Mail: receba alertas de novas mensagens no seu celular. Registre seu aparelho agora! http://br.mobile.yahoo.com/mailalertas/

I dont see how to fix this.
There was a thread about statically knowing lots about the shape of matrices using the type system. http://www.haskell.org/pipermail/haskell/2006-April/017845.html I believe they incorporated this (variable size identity matrix, for example) in their approach. (They don't preserve your property of being able to do things with simple list syntax, like [[1,2],[3,4]] * [[5,6],[7,8]] , instead you have to use Template Haskell and some small contructor functions)
Could be better to forget about fromInteger...
Except then you wouldn't have a full instance for Num. How about constructing an infite list of infinite lists of that number: fromInteger x = map repeat (repeat (fromInteger x)) when it gets zipped with smaller matrices, will it terminate? It works with addition but multiplying caused problems: [[1,2],[3,4]] + 10 = [[11,12],[13,14]] [[1,2],[3,4]] * 10 = [[40,60],[40,60],[40,60],[40,60],[40,60], ..... Hmm... Jared.
Atila
Jared Updike wrote:
fromInteger x = [[fromInteger x]]
Wouldn't you want the expression
[[1,0],[0,2]] + 10
to yield
[[11,10],[10,12]]
instead of [[11]] ? I guess you would need some complicated machinery so this is one thing you have to ignore to keep your otherwise nifty instance nice and simple.
Jared.
-- http://www.updike.org/~jared/ reverse ")-:"

Instead of
fromInteger x = map repeat (repeat (fromInteger x))
I meant
fromInteger x = repeat (repeat (fromInteger x))
but it still doesn't work for multiplication. Jared. -- http://www.updike.org/~jared/ reverse ")-:"

Here is one way to do it. First, you have to interpret operations on matrices as being elementwise applied. E.g, (*) is interpreted as zipWith (zipWith (*)) rather than matrix multiply, and similar for (+) etc. You then obtain a lazy semantics for the operations, where the extent of the resulting matrix is the intersection of the extents of the argument matrices. Second, you lift constants into infinite matrices containing the constant, that is: fromInteger n = repeat (repeat n). Now your examples will work as intended. Björn Lisper Atila Romero:
Good point.
And there is another problem: one could expect 10 * [[1,2],[3,4]] to be equal to [[10,20],[30,40]] and in this case 10 should be equal to [[10,0],[0,10]], instead of [[10,10],[10,10]] or [[10]].
I dont see how to fix this. Could be better to forget about fromInteger...
Atila
Jared Updike wrote:
fromInteger x = [[fromInteger x]]
Wouldn't you want the expression
[[1,0],[0,2]] + 10
to yield
[[11,10],[10,12]]
instead of [[11]] ? I guess you would need some complicated machinery so this is one thing you have to ignore to keep your otherwise nifty instance nice and simple.
Jared.
_______________________________________________________ Novidade no Yahoo! Mail: receba alertas de novas mensagens no seu celular. Registre seu aparelho agora! http://br.mobile.yahoo.com/mailalertas/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I wrote:
Here is one way to do it. First, you have to interpret operations on matrices as being elementwise applied. E.g, (*) is interpreted as zipWith (zipWith (*)) rather than matrix multiply, and similar for (+) etc. You then obtain a lazy semantics for the operations, where the extent of the resulting matrix is the intersection of the extents of the argument matrices. Second, you lift constants into infinite matrices containing the constant, that is: fromInteger n = repeat (repeat n). Now your examples will work as intended.
Ah, should of course be fromInteger n = repeat (repeat (fromInteger n)). Björn Lisper

Bjorn Lisper wrote:
Here is one way to do it. First, you have to interpret operations on matrices as being elementwise applied. E.g, (*) is interpreted as zipWith (zipWith (*)) rather than matrix multiply
What's this, the principle of greatest surprise at work? Nonono, (*) should be matrix multiplication, fromInteger x should be (x * I) and I should be the identity matrix. Now all we need is an infinitely large I, and that gives: instance Num a => Num [[a]] where (+) = zipWith (zipWith (+)) (-) = zipWith (zipWith (-)) negate = map (map negate) fromInteger x = fix (((x : repeat 0) :) . map (0:)) m * n = [ [ sum $ zipWith (*) v w | w <- transpose n ] | v <- m ] Udo.

On Thu, Jun 22, 2006 at 11:57:37AM +0200, Udo Stenzel wrote:
instance Num a => Num [[a]] where (+) = zipWith (zipWith (+)) (-) = zipWith (zipWith (-)) negate = map (map negate) fromInteger x = fix (((x : repeat 0) :) . map (0:)) m * n = [ [ sum $ zipWith (*) v w | w <- transpose n ] | v <- m ]
or perhaps fromInteger x = iterate (0:) (x : repeat 0)

Udo Stenzel:
Bjorn Lisper wrote:
Here is one way to do it. First, you have to interpret operations on matrices as being elementwise applied. E.g, (*) is interpreted as zipWith (zipWith (*)) rather than matrix multiply
What's this, the principle of greatest surprise at work? Nonono, (*) should be matrix multiplication, fromInteger x should be (x * I) and I should be the identity matrix. Now all we need is an infinitely large I, and that gives:
instance Num a => Num [[a]] where (+) = zipWith (zipWith (+)) (-) = zipWith (zipWith (-)) negate = map (map negate) fromInteger x = fix (((x : repeat 0) :) . map (0:)) m * n = [ [ sum $ zipWith (*) v w | w <- transpose n ] | v <- m ]
There are pros and cons, of course. Using (*) for matrix multiply is well-established in linear algebra. But: - it breaks the symmetry. This particular operator is then overloaded in a different way than all the others, and - your definition of fromInteger will behave strangely with the elementwise extended operations, like (+). 1 + [[1,2],[3,4]] will become [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this kind of overloading invariably have the second form of semantics. Björn Lisper

Bjorn Lisper wrote:
- your definition of fromInteger will behave strangely with the elementwise extended operations, like (+). 1 + [[1,2],[3,4]] will become [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this kind of overloading invariably have the second form of semantics.
Don't call an array a matrix. If is named matrix, it should have matrix multiplication, addition, and they should obey the expected laws. Udo. -- Jeder Idiot kann seine Fehler verteidigen, was die meisten Idioten ja auch tun. -- Dale Carnegie

Udo Stenzel:
Bjorn Lisper wrote:
- your definition of fromInteger will behave strangely with the elementwise extended operations, like (+). 1 + [[1,2],[3,4]] will become [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this kind of overloading invariably have the second form of semantics.
Don't call an array a matrix. If is named matrix, it should have matrix multiplication, addition, and they should obey the expected laws.
But you still have the problem with the overloading of constants in your proposal. If you write 17 + a, where a is a matrix, what do people in general expect it to be? Björn Lisper

Although there *could* be a fromInteger default behavior, there isn't a mathematical default behavior to c+A. An even c*A it's hard to make work, because an identity matrix only works if it is a square matrix. Example, if in c*A we make A= 1 3 2 4 and c= c 0 0 0 ... 0 c 0 0 ... 0 0 c 0 ... 0 0 0 c ... ... the result will have 2 lines and infinite columns. And if we make A*c the result will have 2 columns and infinite lines. And since there's no way to tell to fromInteger which size we need for c, there's no way to make fromInteger works in a intuitive way. So, I think it's better to just not use fromInteger at all, because it will work at some cases but will give wrong results at others. Atila Bjorn Lisper wrote:
Udo Stenzel:
Bjorn Lisper wrote:
- your definition of fromInteger will behave strangely with the elementwise extended operations, like (+). 1 + [[1,2],[3,4]] will become [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this kind of overloading invariably have the second form of semantics.
Don't call an array a matrix. If is named matrix, it should have matrix multiplication, addition, and they should obey the expected laws.
But you still have the problem with the overloading of constants in your proposal. If you write 17 + a, where a is a matrix, what do people in general expect it to be?
Björn Lisper _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________________ Yahoo! Acesso Grátis - Internet rápida e grátis. Instale o discador agora! http://br.acesso.yahoo.com

Mathematically the least surprising thing for matrices/arrays is (fromInteger 0) * a{- n by m Matrix -} = "0"{- n by m Matrix -} (fromInteger 1) * a{- n by m Matrix -} = a{- n by m Matrix -} Thus I would want (fromInteger 1) in this case to make an Identity {- n by n Matrix -} matrix. And then (fromInteger i) to be a diagonal n by n matrix of all i's. There is no reason to have infinite columns or rows from (fromInteger i), it would only produce square diagonal matrices with i on the diagonal. This has the very nice property that Num ops "lift" from integer to matrices: For type Matrix: 2+3 == 5, 2*3 == 6, 2*(6-3) == (2*6)-(2*3) == (negate 6), etc. and (negate (fromInteger 4)) == (fromInteger (negate 4)) Mathematically, I can't remember ever wanting to add x to every entry in a matrix. Remeber: (+) and (*) have type "Matrix -> Matrix -> Matrix". If you want to add Int to Matrix then you should really define a new operator for that. Note: For a purist Num should be commutative, which means only square Matrices are allowed. If you must use (*) and (+) in bizarre ways, then you could hide the Prelude and substitute your own Math type classes that know how to mix your types. Atila Romero wrote:
Although there *could* be a fromInteger default behavior, there isn't a mathematical default behavior to c+A. An even c*A it's hard to make work, because an identity matrix only works if it is a square matrix. Example, if in c*A we make A= 1 3 2 4 and c= c 0 0 0 ... 0 c 0 0 ... 0 0 c 0 ... 0 0 0 c ... ... the result will have 2 lines and infinite columns. And if we make A*c the result will have 2 columns and infinite lines. And since there's no way to tell to fromInteger which size we need for c, there's no way to make fromInteger works in a intuitive way.
So, I think it's better to just not use fromInteger at all, because it will work at some cases but will give wrong results at others.
Atila
Bjorn Lisper wrote:
Udo Stenzel:
Bjorn Lisper wrote:
- your definition of fromInteger will behave strangely with the elementwise extended operations, like (+). 1 + [[1,2],[3,4]] will become [[2,2],[3,5]] rather than [[2,3],[4,5]]. Array languages supporting this kind of overloading invariably have the second form of semantics.
Don't call an array a matrix. If is named matrix, it should have matrix multiplication, addition, and they should obey the expected laws.
But you still have the problem with the overloading of constants in your proposal. If you write 17 + a, where a is a matrix, what do people in general expect it to be?
Björn Lispe

Jared Updike wrote:
Wouldn't you want the expression
[[1,0],[0,2]] + 10 to yield [[11,10],[10,12]]
You could handle this as a special case in (+) and (*), but this is kind of a hack. Something like:
(+) [[x]] y = map (map (x+)) y (+) x [[y]] = map (map (+y)) x (+) x y = zipWith (zipWith (+)) x y
Twan

Sorry, this was originally only sent to Atila, due to me pressing the
wrong button.
On 21/06/06, Atila Romero
instance Num a => Num [[a]] where fromInteger x = [[fromInteger x]] abs x = map (map abs) x (+) [ ] y = y (+) x [ ] = x (+) x y = zipWith (zipWith (+)) x y (*) x y = map (matrixXvector x) y where -- matrixXvector :: Num a => [[a]] -> [a] -> [[a]] matrixXvector m v = foldl vectorsum [] $ zipWith vectorXnumber m v -- vectorXnumber :: Num a => [a] -> a -> [a] vectorXnumber v n = map (n*) v -- vectorsum :: [a] -> [a] -> [a] vectorsum [] y = y vectorsum x [] = x vectorsum x y = zipWith (+) x y
Just a couple of comments: * You don't have to comment out the type signitures, they're perfectly valid in let and where clauses. * Infix functions, as well as being used infix, can be defined infix too. I.e., you could have written x * y = map (matrixXvector x) y. * Zipping the empty list with anything produces the empty list, so your two equations for (*) involving the empty list are redundant. * You define vectorsum, but don't seem to use it anywhere. -- -David House, dmhouse@gmail.com

Sorry, a few corrections to my above points:
On 21/06/06, David House
* Zipping the empty list with anything produces the empty list, so your two equations for (*) involving the empty list are redundant.
I meant (+).
* You define vectorsum, but don't seem to use it anywhere.
Disregard this. -- -David House, dmhouse@gmail.com

Well, I was forcing A+[[]] to be A instead of [[]]. But who would do that kind of thing anyway? So I agree with you, those 2 (+) lines are useless. Atila David House wrote:
Sorry, a few corrections to my above points:
On 21/06/06, David House
wrote: * Zipping the empty list with anything produces the empty list, so your two equations for (*) involving the empty list are redundant.
I meant (+).
* You define vectorsum, but don't seem to use it anywhere.
Disregard this.
_______________________________________________________ Yahoo! doce lar. Faça do Yahoo! sua homepage. http://br.yahoo.com/homepageset.html
participants (8)
-
Atila Romero
-
Bjorn Lisper
-
Chris Kuklewicz
-
David House
-
Jared Updike
-
Ross Paterson
-
Twan van Laarhoven
-
Udo Stenzel