summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2008-02-23 19:35:51 +0000
committerAlberto Ruiz <aruiz@um.es>2008-02-23 19:35:51 +0000
commit500f5fca244dadab494655aa73d7183df1c87c50 (patch)
treee02abfcf4db24a538646c6f0982c58dabb3adc63 /lib
parentda54e2f2c27f68c08f4db7551c57b2c1136dc778 (diff)
working on tests
Diffstat (limited to 'lib')
-rw-r--r--lib/Numeric/LinearAlgebra/Algorithms.hs2
-rw-r--r--lib/Numeric/LinearAlgebra/Tests.hs61
-rw-r--r--lib/Numeric/LinearAlgebra/Tests/Instances.hs63
-rw-r--r--lib/Numeric/LinearAlgebra/Tests/Properties.hs70
4 files changed, 157 insertions, 39 deletions
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs
index 79cc64d..1de018c 100644
--- a/lib/Numeric/LinearAlgebra/Algorithms.hs
+++ b/lib/Numeric/LinearAlgebra/Algorithms.hs
@@ -142,7 +142,7 @@ eigSH m | m `equal` ctrans m = eigSH' m
142 142
143-- | Cholesky factorization of a positive definite hermitian or symmetric matrix using lapack's dpotrf or zportrf. 143-- | Cholesky factorization of a positive definite hermitian or symmetric matrix using lapack's dpotrf or zportrf.
144-- 144--
145-- If @c = chol m@ then @m == c \<> ctrans c@. 145-- If @c = chol m@ then @m == ctrans c \<> c@.
146chol :: Field t => Matrix t -> Matrix t 146chol :: Field t => Matrix t -> Matrix t
147chol m | m `equal` ctrans m = cholSH m 147chol m | m `equal` ctrans m = cholSH m
148 | otherwise = error "chol requires positive definite complex hermitian or real symmetric matrix" 148 | otherwise = error "chol requires positive definite complex hermitian or real symmetric matrix"
diff --git a/lib/Numeric/LinearAlgebra/Tests.hs b/lib/Numeric/LinearAlgebra/Tests.hs
index 534eb04..7ecf812 100644
--- a/lib/Numeric/LinearAlgebra/Tests.hs
+++ b/lib/Numeric/LinearAlgebra/Tests.hs
@@ -15,8 +15,7 @@ Some tests.
15module Numeric.LinearAlgebra.Tests( 15module Numeric.LinearAlgebra.Tests(
16 module Numeric.LinearAlgebra.Tests.Instances, 16 module Numeric.LinearAlgebra.Tests.Instances,
17 module Numeric.LinearAlgebra.Tests.Properties, 17 module Numeric.LinearAlgebra.Tests.Properties,
18 qCheck,RM,CM, rM,cM, rHer,cHer,rRot,cRot,rSq,cSq, 18 qCheck, runTests
19 runTests
20--, runBigTests 19--, runBigTests
21) where 20) where
22 21
@@ -24,43 +23,41 @@ import Numeric.LinearAlgebra
24import Numeric.LinearAlgebra.Tests.Instances 23import Numeric.LinearAlgebra.Tests.Instances
25import Numeric.LinearAlgebra.Tests.Properties 24import Numeric.LinearAlgebra.Tests.Properties
26import Test.QuickCheck 25import Test.QuickCheck
27import Debug.Trace 26import Numeric.GSL(setErrorHandlerOff)
28 27
29qCheck n = check defaultConfig {configSize = const n} 28qCheck n = check defaultConfig {configSize = const n}
30 29
31debug x = trace (show x) x
32
33type RM = Matrix Double
34type CM = Matrix (Complex Double)
35
36rM m = m :: RM
37cM m = m :: CM
38
39rHer (Her m) = m :: RM
40cHer (Her m) = m :: CM
41
42rRot (Rot m) = m :: RM
43cRot (Rot m) = m :: CM
44
45rSq (Sq m) = m :: RM
46cSq (Sq m) = m :: CM
47
48rWC (WC m) = m :: RM
49cWC (WC m) = m :: CM
50
51-- | It runs all the tests. 30-- | It runs all the tests.
52runTests :: Int -- ^ maximum dimension 31runTests :: Int -- ^ maximum dimension
53 -> IO () 32 -> IO ()
54runTests n = do 33runTests n = do
55 qCheck n (hermitian . rHer) 34 setErrorHandlerOff
56 qCheck n (hermitian . cHer) 35 let test p = qCheck n p
57 qCheck n (unitary . rRot) 36 test (luProp . rM)
58 qCheck n (unitary . cRot) 37 test (luProp . cM)
59 qCheck n (wellCond . rWC) 38 test (invProp . rSqWC)
60 qCheck n (wellCond . cWC) 39 test (invProp . cSqWC)
61 -------------------------------- 40 test (pinvProp . rM)
62 qCheck n (luTest . rM) 41 test (pinvProp . cM)
63 qCheck n (luTest . cM) 42 test (detProp . cSqWC)
43 test (svdProp1 . rM)
44 test (svdProp1 . cM)
45 test (svdProp2 . rM)
46 test (svdProp2 . cM)
47 test (eigSHProp . rHer)
48 test (eigSHProp . cHer)
49 test (eigProp . rSq)
50 test (eigProp . cSq)
51 test (nullspaceProp . rM)
52 test (nullspaceProp . cM)
53 test (qrProp . rM)
54 test (qrProp . cM)
55 test (hessProp . rSq)
56 test (hessProp . cSq)
57 test (schurProp2 . rSq)
58 test (schurProp1 . cSq)
59 test (cholProp . rPosDef)
60 test (cholProp . cPosDef)
64 61
65-- | Some additional tests on big matrices. They take a few minutes. 62-- | Some additional tests on big matrices. They take a few minutes.
66runBigTests :: IO () 63runBigTests :: IO ()
diff --git a/lib/Numeric/LinearAlgebra/Tests/Instances.hs b/lib/Numeric/LinearAlgebra/Tests/Instances.hs
index 583143a..af486c8 100644
--- a/lib/Numeric/LinearAlgebra/Tests/Instances.hs
+++ b/lib/Numeric/LinearAlgebra/Tests/Instances.hs
@@ -14,10 +14,13 @@ Arbitrary instances for vectors, matrices.
14-} 14-}
15 15
16module Numeric.LinearAlgebra.Tests.Instances( 16module Numeric.LinearAlgebra.Tests.Instances(
17 Sq(..), 17 Sq(..), rSq,cSq,
18 Rot(..), 18 Rot(..), rRot,cRot,
19 Her(..), 19 Her(..), rHer,cHer,
20 WC(..) 20 WC(..), rWC,cWC,
21 SqWC(..), rSqWC, cSqWC,
22 PosDef(..), rPosDef, cPosDef,
23 RM,CM, rM,cM
21) where 24) where
22 25
23import Numeric.LinearAlgebra 26import Numeric.LinearAlgebra
@@ -74,7 +77,7 @@ instance (Field a, Arbitrary a) => Arbitrary (Her a) where
74 return $ Her (m' + ctrans m') 77 return $ Her (m' + ctrans m')
75 coarbitrary = undefined 78 coarbitrary = undefined
76 79
77-- a well-conditioned matrix (the singular values are between 1 and 100) 80-- a well-conditioned general matrix (the singular values are between 1 and 100)
78newtype (WC a) = WC (Matrix a) deriving Show 81newtype (WC a) = WC (Matrix a) deriving Show
79instance (Field a, Arbitrary a) => Arbitrary (WC a) where 82instance (Field a, Arbitrary a) => Arbitrary (WC a) where
80 arbitrary = do 83 arbitrary = do
@@ -87,3 +90,53 @@ instance (Field a, Arbitrary a) => Arbitrary (WC a) where
87 let s = diagRect (fromList sv) r c 90 let s = diagRect (fromList sv) r c
88 return $ WC (u <> real s <> trans v) 91 return $ WC (u <> real s <> trans v)
89 coarbitrary = undefined 92 coarbitrary = undefined
93
94-- a well-conditioned square matrix (the singular values are between 1 and 100)
95newtype (SqWC a) = SqWC (Matrix a) deriving Show
96instance (Field a, Arbitrary a) => Arbitrary (SqWC a) where
97 arbitrary = do
98 Sq m <- arbitrary
99 let (u,_,v) = svd m
100 n = rows m
101 sv <- replicateM n (choose (1,100))
102 let s = diag (fromList sv)
103 return $ SqWC (u <> real s <> trans v)
104 coarbitrary = undefined
105
106-- a positive definite square matrix (the eigenvalues are between 0 and 100)
107newtype (PosDef a) = PosDef (Matrix a) deriving Show
108instance (Field a, Arbitrary a) => Arbitrary (PosDef a) where
109 arbitrary = do
110 Her m <- arbitrary
111 let (_,v) = eigSH m
112 n = rows m
113 l <- replicateM n (choose (0,100))
114 let s = diag (fromList l)
115 p = v <> real s <> ctrans v
116 return $ PosDef (0.5 .* p + 0.5 .* ctrans p)
117 coarbitrary = undefined
118
119type RM = Matrix Double
120type CM = Matrix (Complex Double)
121
122rM m = m :: RM
123cM m = m :: CM
124
125rHer (Her m) = m :: RM
126cHer (Her m) = m :: CM
127
128rRot (Rot m) = m :: RM
129cRot (Rot m) = m :: CM
130
131rSq (Sq m) = m :: RM
132cSq (Sq m) = m :: CM
133
134rWC (WC m) = m :: RM
135cWC (WC m) = m :: CM
136
137rSqWC (SqWC m) = m :: RM
138cSqWC (SqWC m) = m :: CM
139
140rPosDef (PosDef m) = m :: RM
141cPosDef (PosDef m) = m :: CM
142
diff --git a/lib/Numeric/LinearAlgebra/Tests/Properties.hs b/lib/Numeric/LinearAlgebra/Tests/Properties.hs
index 351615b..0317469 100644
--- a/lib/Numeric/LinearAlgebra/Tests/Properties.hs
+++ b/lib/Numeric/LinearAlgebra/Tests/Properties.hs
@@ -19,6 +19,7 @@ where
19 19
20import Numeric.LinearAlgebra 20import Numeric.LinearAlgebra
21import Numeric.LinearAlgebra.Tests.Instances(Sq(..),Her(..),Rot(..)) 21import Numeric.LinearAlgebra.Tests.Instances(Sq(..),Her(..),Rot(..))
22import Test.QuickCheck
22 23
23-- relative error 24-- relative error
24dist :: (Normed t, Num t) => t -> t -> Double 25dist :: (Normed t, Num t) => t -> t -> Double
@@ -53,7 +54,74 @@ degenerate m = rank m < min (rows m) (cols m)
53 54
54wellCond m = rcond m > 1/100 55wellCond m = rcond m > 1/100
55 56
57positiveDefinite m = minimum (toList e) > 0
58 where (e,v) = eigSH m
59
60upperTriang m = rows m == 1 || down == z
61 where down = fromList $ concat $ zipWith drop [1..] (toLists (ctrans m))
62 z = constant 0 (dim down)
63
64upperHessenberg m = rows m < 3 || down == z
65 where down = fromList $ concat $ zipWith drop [2..] (toLists (ctrans m))
66 z = constant 0 (dim down)
67
68zeros (r,c) = reshape c (constant 0 (r*c))
69
70ones (r,c) = zeros (r,c) + 1
71
56----------------------------------------------------- 72-----------------------------------------------------
57 73
58luTest m = m |~| p <> l <> u && det p == s 74luProp m = m |~| p <> l <> u && det p == s
59 where (l,u,p,s) = lu m 75 where (l,u,p,s) = lu m
76
77invProp m = m <> inv m |~| ident (rows m)
78
79pinvProp m = m <> p <> m |~| m
80 && p <> m <> p |~| p
81 && hermitian (m<>p)
82 && hermitian (p<>m)
83 where p = pinv m
84
85detProp m = s d1 |~| s d2
86 where d1 = det m
87 d2 = det' m * det q
88 det' m = product $ toList $ takeDiag r
89 (q,r) = qr m
90 s x = fromList [x]
91
92nullspaceProp m = null nl `trivial` (null nl || m <> n |~| zeros (r,c))
93 where nl = nullspacePrec 1 m
94 n = fromColumns nl
95 r = rows m
96 c = cols m - rank m
97
98svdProp1 m = u <> real d <> trans v |~| m
99 && unitary u && unitary v
100 where (u,d,v) = full svd m
101
102svdProp2 m = (m |~| 0) `trivial` ((m |~| 0) || u <> real (diag s) <> trans v |~| m)
103 where (u,s,v) = economy svd m
104
105eigProp m = complex m <> v |~| v <> diag s
106 where (s, v) = eig m
107
108eigSHProp m = m <> v |~| v <> real (diag s)
109 && unitary v
110 && m |~| v <> real (diag s) <> ctrans v
111 where (s, v) = eigSH m
112
113qrProp m = q <> r |~| m && unitary q && upperTriang r
114 where (q,r) = qr m
115
116hessProp m = m |~| p <> h <> ctrans p && unitary p && upperHessenberg h
117 where (p,h) = hess m
118
119schurProp1 m = m |~| u <> s <> ctrans u && unitary u && upperTriang s
120 where (u,s) = schur m
121
122schurProp2 m = m |~| u <> s <> ctrans u && unitary u && upperHessenberg s -- fixme
123 where (u,s) = schur m
124
125cholProp m = m |~| ctrans c <> c && upperTriang c
126 where c = chol m
127 pos = positiveDefinite m