Sorry, this was originally only sent to Atila, due to me pressing the
wrong button.

On 21/06/06, Atila Romero <[EMAIL PROTECTED]> wrote:
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, [EMAIL PROTECTED]
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to