summaryrefslogtreecommitdiff
path: root/examples/tests.hs
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2007-11-30 19:55:34 +0000
committerAlberto Ruiz <aruiz@um.es>2007-11-30 19:55:34 +0000
commitd7d3b731c037fca41bd9128c3da2a582189cb4d9 (patch)
treef1bf8f1fa538033ff184d6cc556e808bfaaa71a9 /examples/tests.hs
parent975d3730a923387f9d1a0be4f7d11b01b27a09df (diff)
hide internal modules
Diffstat (limited to 'examples/tests.hs')
-rw-r--r--examples/tests.hs26
1 files changed, 19 insertions, 7 deletions
diff --git a/examples/tests.hs b/examples/tests.hs
index 2d6b7e9..60bef8f 100644
--- a/examples/tests.hs
+++ b/examples/tests.hs
@@ -2,19 +2,19 @@
2 2
3module Main where 3module Main where
4 4
5import Data.Packed.Internal((>|<), multiply', multiplyG, MatrixOrder(..),debug,fmat)
6import Numeric.GSL hiding (sin,cos,exp,choose) 5import Numeric.GSL hiding (sin,cos,exp,choose)
7import Numeric.LinearAlgebra 6import Numeric.LinearAlgebra
8import Numeric.LinearAlgebra.Linear(Linear)
9import Numeric.LinearAlgebra.LAPACK 7import Numeric.LinearAlgebra.LAPACK
10import Numeric.GSL.Matrix(svdg)
11import qualified Numeric.GSL.Matrix as GSL 8import qualified Numeric.GSL.Matrix as GSL
12import Test.QuickCheck hiding (test) 9import Test.QuickCheck hiding (test)
13import Test.HUnit hiding ((~:),test) 10import Test.HUnit hiding ((~:),test)
14import System.Random(randomRs,mkStdGen) 11import System.Random(randomRs,mkStdGen)
15import System.Info 12import System.Info
16import Data.List(foldl1') 13import Data.List(foldl1', transpose)
17import System(getArgs) 14import System(getArgs)
15import Debug.Trace(trace)
16
17debug x = trace (show x) x
18 18
19type RM = Matrix Double 19type RM = Matrix Double
20type CM = Matrix (Complex Double) 20type CM = Matrix (Complex Double)
@@ -340,8 +340,20 @@ expmTestDiag m = expm (logm m) |~| complex m
340asFortran m = (rows m >|< cols m) $ toList (flatten $ trans m) 340asFortran m = (rows m >|< cols m) $ toList (flatten $ trans m)
341asC m = (rows m >< cols m) $ toList (flatten m) 341asC m = (rows m >< cols m) $ toList (flatten m)
342 342
343mulC a b = multiply' RowMajor a b 343mulC a b = a <> b
344mulF a b = multiply' ColumnMajor a b 344mulF a b = trans $ trans b <> trans a
345
346-------------------------------------------------------------------------
347
348multiplyG a b = reshape (cols b) $ fromList $ concat $ multiplyL (toLists a) (toLists b)
349 where multiplyL a b = [[dotL x y | y <- transpose b] | x <- a]
350 dotL a b = sum (zipWith (*) a b)
351
352r >|< c = f where
353 f l | dim v == r*c = reshapeF r v
354 | otherwise = error "(>|<)"
355 where v = fromList l
356 reshapeF r = trans . reshape r
345 357
346--------------------------------------------------------------------- 358---------------------------------------------------------------------
347 359
@@ -389,7 +401,7 @@ tests = do
389 quickCheck (svdTest' svdR) 401 quickCheck (svdTest' svdR)
390 quickCheck (svdTest' svdRdd) 402 quickCheck (svdTest' svdRdd)
391 quickCheck (svdTest' svdC) 403 quickCheck (svdTest' svdC)
392 quickCheck (svdTest' svdg) 404 quickCheck (svdTest' GSL.svdg)
393 putStrLn "--------- eig ---------" 405 putStrLn "--------- eig ---------"
394 quickCheck (eigTest . sqm :: SqM Double -> Bool) 406 quickCheck (eigTest . sqm :: SqM Double -> Bool)
395 quickCheck (eigTest . sqm :: SqM (Complex Double) -> Bool) 407 quickCheck (eigTest . sqm :: SqM (Complex Double) -> Bool)