
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/