summaryrefslogtreecommitdiff
path: root/examples
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2007-06-09 12:10:58 +0000
committerAlberto Ruiz <aruiz@um.es>2007-06-09 12:10:58 +0000
commit7931a9b18ea84ed5f49e2803ba596f190567d9d8 (patch)
tree64a08a62b2bffcf48becbab03933f3c7b4527a73 /examples
parente21f42f742959ec9452add9b6c6e08d30d9584ed (diff)
more tests
Diffstat (limited to 'examples')
-rw-r--r--examples/tests.hs149
1 files changed, 149 insertions, 0 deletions
diff --git a/examples/tests.hs b/examples/tests.hs
new file mode 100644
index 0000000..f167b92
--- /dev/null
+++ b/examples/tests.hs
@@ -0,0 +1,149 @@
1--
2-- QuickCheck tests
3--
4
5-----------------------------------------------------------------------------
6
7import Data.Packed.Internal.Vector
8import Data.Packed.Internal.Matrix
9import LAPACK
10import Test.QuickCheck
11import Complex
12
13{-
14-- Bravo por quickCheck!
15
16pinvProp1 tol m = (rank m == cols m) ==> pinv m <> m ~~ ident (cols m)
17 where infix 2 ~~
18 (~~) = approxEqual tol
19
20pinvProp2 tol m = 0 < r && r <= c ==> (r==c) `trivial` (m <> pinv m <> m ~~ m)
21 where r = rank m
22 c = cols m
23 infix 2 ~~
24 (~~) = approxEqual tol
25
26nullspaceProp tol m = cr > 0 ==> m <> nt ~~ zeros
27 where nt = trans (nullspace m)
28 cr = corank m
29 r = rows m
30 zeros = create [r,cr] $ replicate (r*cr) 0
31
32-}
33
34r >< c = f where
35 f l | dim v == r*c = matrixFromVector RowMajor c v
36 | otherwise = error $ "inconsistent list size = "
37 ++show (dim v) ++"in ("++show r++"><"++show c++")"
38 where v = fromList l
39
40r >|< c = f where
41 f l | dim v == r*c = matrixFromVector ColumnMajor c v
42 | otherwise = error $ "inconsistent list size = "
43 ++show (dim v) ++"in ("++show r++"><"++show c++")"
44 where v = fromList l
45
46ac = (2><3) [1 .. 6::Double]
47bc = (3><4) [7 .. 18::Double]
48
49mz = (2 >< 3) [1,2,3,4,5,6:+(1::Double)]
50
51af = (2>|<3) [1,4,2,5,3,6::Double]
52bf = (3>|<4) [7,11,15,8,12,16,9,13,17,10,14,18::Double]
53
54a |=| b = rows a == rows b &&
55 cols a == cols b &&
56 toList (cdat a) == toList (cdat b) &&
57 toList (fdat a) == toList (fdat b)
58
59aprox fun a b = rows a == rows b &&
60 cols a == cols b &&
61 eps > aproxL fun (toList (t a)) (toList (t b))
62 where t = if (order a == RowMajor) `xor` isTrans a then cdat else fdat
63
64aproxL fun v1 v2 = sum (zipWith (\a b-> fun (a-b)) v1 v2) / fromIntegral (length v1)
65
66(|~|) = aprox abs
67(|~~|) = aprox magnitude
68
69eps = 1E-8::Double
70
71asFortran m = (rows m >|< cols m) $ toList (fdat m)
72asC m = (rows m >< cols m) $ toList (cdat m)
73
74mulC a b = multiply RowMajor a b
75mulF a b = multiply ColumnMajor a b
76
77cc = mulC ac bf
78cf = mulF af bc
79
80r = mulC cc (trans cf)
81
82ident n = diag (constant n 1)
83
84rd = (2><2)
85 [ 43492.0, 50572.0
86 , 102550.0, 119242.0 :: Double]
87
88instance (Arbitrary a, RealFloat a) => Arbitrary (Complex a) where
89 arbitrary = do
90 r <- arbitrary
91 i <- arbitrary
92 return (r:+i)
93 coarbitrary = undefined
94
95instance (Field a, Arbitrary a) => Arbitrary (Matrix a) where
96 arbitrary = do --m <- sized $ \max -> choose (1,1+3*max)
97 m <- choose (1,10)
98 n <- choose (1,10)
99 l <- vector (m*n)
100 ctype <- arbitrary
101 let h = if ctype then (m><n) else (m>|<n)
102 trMode <- arbitrary
103 let tr = if trMode then trans else id
104 return $ tr (h l)
105 coarbitrary = undefined
106
107data PairM a = PairM (Matrix a) (Matrix a) deriving Show
108instance (Num a, Field a, Arbitrary a) => Arbitrary (PairM a) where
109 arbitrary = do
110 a <- choose (1,10)
111 b <- choose (1,10)
112 c <- choose (1,10)
113 l1 <- vector (a*b)
114 l2 <- vector (b*c)
115 return $ PairM ((a><b) (map fromIntegral (l1::[Int]))) ((b><c) (map fromIntegral (l2::[Int])))
116 --return $ PairM ((a><b) l1) ((b><c) l2)
117 coarbitrary = undefined
118
119type BaseType = Double
120
121
122svdTestR fun prod m = u <> s <> trans v |~| m
123 && u <> trans u |~| ident (rows m)
124 && v <> trans v |~| ident (cols m)
125 where (u,s,v) = fun m
126 (<>) = prod
127
128
129svdTestC fun prod m = u <> s' <> (trans v) |~~| m
130 && u <> (liftMatrix conj) (trans u) |~~| ident (rows m)
131 && v <> (liftMatrix conj) (trans v) |~~| ident (cols m)
132 where (u,s,v) = fun m
133 (<>) = prod
134 s' = liftMatrix comp s
135
136comp v = toComplex (v,constant (dim v) 0)
137
138main = do
139 quickCheck $ \l -> null l || (toList . fromList) l == (l :: [BaseType])
140 quickCheck $ \m -> m |=| asC (m :: Matrix BaseType)
141 quickCheck $ \m -> m |=| asFortran (m :: Matrix BaseType)
142 quickCheck $ \m -> m |=| (asC . asFortran) (m :: Matrix BaseType)
143 quickCheck $ \(PairM m1 m2) -> mulC m1 m2 |=| mulF m1 (m2 :: Matrix BaseType)
144 quickCheck $ \(PairM m1 m2) -> mulC m1 m2 |=| trans (mulF (trans m2) (trans m1 :: Matrix BaseType))
145 quickCheck $ \(PairM m1 m2) -> mulC m1 m2 |=| multiplyG m1 (m2 :: Matrix BaseType)
146 quickCheck (svdTestR svdR mulC)
147 quickCheck (svdTestR svdR mulF)
148 quickCheck (svdTestC svdC mulC)
149 quickCheck (svdTestC svdC mulF)