diff options
Diffstat (limited to 'lib/Numeric/LinearAlgebra')
-rw-r--r-- | lib/Numeric/LinearAlgebra/Algorithms.hs | 2 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/LAPACK.hs | 1 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Linear.hs | 67 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Tests/Instances.hs | 14 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Tests/Properties.hs | 6 |
5 files changed, 52 insertions, 38 deletions
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs index ac46847..8306961 100644 --- a/lib/Numeric/LinearAlgebra/Algorithms.hs +++ b/lib/Numeric/LinearAlgebra/Algorithms.hs | |||
@@ -85,7 +85,7 @@ import Numeric.Vector | |||
85 | import Numeric.Matrix() | 85 | import Numeric.Matrix() |
86 | 86 | ||
87 | -- | Auxiliary typeclass used to define generic computations for both real and complex matrices. | 87 | -- | Auxiliary typeclass used to define generic computations for both real and complex matrices. |
88 | class (Product t, Linear Vector t, Linear Matrix t) => Field t where | 88 | class (Product t, Linear Vector t, Container Vector t, Container Matrix t) => Field t where |
89 | svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t) | 89 | svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t) |
90 | thinSVD' :: Matrix t -> (Matrix t, Vector Double, Matrix t) | 90 | thinSVD' :: Matrix t -> (Matrix t, Vector Double, Matrix t) |
91 | sv' :: Matrix t -> Vector Double | 91 | sv' :: Matrix t -> Vector Double |
diff --git a/lib/Numeric/LinearAlgebra/LAPACK.hs b/lib/Numeric/LinearAlgebra/LAPACK.hs index 8888712..5d0154d 100644 --- a/lib/Numeric/LinearAlgebra/LAPACK.hs +++ b/lib/Numeric/LinearAlgebra/LAPACK.hs | |||
@@ -44,6 +44,7 @@ module Numeric.LinearAlgebra.LAPACK ( | |||
44 | import Data.Packed.Internal | 44 | import Data.Packed.Internal |
45 | import Data.Packed.Matrix | 45 | import Data.Packed.Matrix |
46 | import Data.Complex | 46 | import Data.Complex |
47 | import Numeric.Vector() | ||
47 | import Numeric.Container | 48 | import Numeric.Container |
48 | import Numeric.GSL.Vector(vectorMapValR, FunCodeSV(Scale)) | 49 | import Numeric.GSL.Vector(vectorMapValR, FunCodeSV(Scale)) |
49 | import Foreign | 50 | import Foreign |
diff --git a/lib/Numeric/LinearAlgebra/Linear.hs b/lib/Numeric/LinearAlgebra/Linear.hs index 952661d..775060e 100644 --- a/lib/Numeric/LinearAlgebra/Linear.hs +++ b/lib/Numeric/LinearAlgebra/Linear.hs | |||
@@ -18,7 +18,7 @@ Basic optimized operations on vectors and matrices. | |||
18 | 18 | ||
19 | module Numeric.LinearAlgebra.Linear ( | 19 | module Numeric.LinearAlgebra.Linear ( |
20 | -- * Linear Algebra Typeclasses | 20 | -- * Linear Algebra Typeclasses |
21 | Vectors(..), Linear(..), | 21 | Vectors(..), |
22 | -- * Products | 22 | -- * Products |
23 | Product(..), | 23 | Product(..), |
24 | mXm,mXv,vXm, | 24 | mXm,mXv,vXm, |
@@ -34,22 +34,52 @@ import Data.Packed.Matrix | |||
34 | import Data.Packed.Vector | 34 | import Data.Packed.Vector |
35 | import Data.Complex | 35 | import Data.Complex |
36 | import Numeric.Container | 36 | import Numeric.Container |
37 | --import Numeric.Vector | 37 | import Numeric.Vector() |
38 | --import Numeric.Matrix | 38 | import Numeric.Matrix() |
39 | --import Numeric.GSL.Vector | 39 | import Numeric.GSL.Vector |
40 | import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ) | 40 | import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ) |
41 | 41 | ||
42 | -- | basic Vector functions | 42 | -- | Linear algebraic properties of objects |
43 | class Num e => Vectors a e where | 43 | class Num e => Vectors a e where |
44 | -- the C functions sumX are twice as fast as using foldVector | 44 | -- | dot (inner) product |
45 | vectorSum :: a e -> e | ||
46 | vectorProd :: a e -> e | ||
47 | absSum :: a e -> e | ||
48 | dot :: a e -> a e -> e | 45 | dot :: a e -> a e -> e |
46 | -- | sum of absolute value of elements (differs in complex case from @norm1@ | ||
47 | absSum :: a e -> e | ||
48 | -- | sum of absolute value of elements | ||
49 | norm1 :: a e -> e | 49 | norm1 :: a e -> e |
50 | -- | euclidean norm | ||
50 | norm2 :: a e -> e | 51 | norm2 :: a e -> e |
52 | -- | element of maximum magnitude | ||
51 | normInf :: a e -> e | 53 | normInf :: a e -> e |
52 | 54 | ||
55 | instance Vectors Vector Float where | ||
56 | norm2 = toScalarF Norm2 | ||
57 | absSum = toScalarF AbsSum | ||
58 | dot = dotF | ||
59 | norm1 = toScalarF AbsSum | ||
60 | normInf = maxElement . vectorMapF Abs | ||
61 | |||
62 | instance Vectors Vector Double where | ||
63 | norm2 = toScalarR Norm2 | ||
64 | absSum = toScalarR AbsSum | ||
65 | dot = dotR | ||
66 | norm1 = toScalarR AbsSum | ||
67 | normInf = maxElement . vectorMapR Abs | ||
68 | |||
69 | instance Vectors Vector (Complex Float) where | ||
70 | norm2 = (:+ 0) . toScalarQ Norm2 | ||
71 | absSum = (:+ 0) . toScalarQ AbsSum | ||
72 | dot = dotQ | ||
73 | norm1 = (:+ 0) . sumElements . fst . fromComplex . vectorMapQ Abs | ||
74 | normInf = (:+ 0) . maxElement . fst . fromComplex . vectorMapQ Abs | ||
75 | |||
76 | instance Vectors Vector (Complex Double) where | ||
77 | norm2 = (:+ 0) . toScalarC Norm2 | ||
78 | absSum = (:+ 0) . toScalarC AbsSum | ||
79 | dot = dotC | ||
80 | norm1 = (:+ 0) . sumElements . fst . fromComplex . vectorMapC Abs | ||
81 | normInf = (:+ 0) . maxElement . fst . fromComplex . vectorMapC Abs | ||
82 | |||
53 | ---------------------------------------------------- | 83 | ---------------------------------------------------- |
54 | 84 | ||
55 | class Element t => Product t where | 85 | class Element t => Product t where |
@@ -128,22 +158,3 @@ kronecker a b = fromBlocks | |||
128 | 158 | ||
129 | 159 | ||
130 | ------------------------------------------------------------------- | 160 | ------------------------------------------------------------------- |
131 | |||
132 | |||
133 | -- | Basic element-by-element functions. | ||
134 | class (Element e, Container c e) => Linear c e where | ||
135 | -- | create a structure with a single element | ||
136 | scalar :: e -> c e | ||
137 | scale :: e -> c e -> c e | ||
138 | -- | scale the element by element reciprocal of the object: | ||
139 | -- | ||
140 | -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@ | ||
141 | scaleRecip :: e -> c e -> c e | ||
142 | addConstant :: e -> c e -> c e | ||
143 | add :: c e -> c e -> c e | ||
144 | sub :: c e -> c e -> c e | ||
145 | -- | element by element multiplication | ||
146 | mul :: c e -> c e -> c e | ||
147 | -- | element by element division | ||
148 | divide :: c e -> c e -> c e | ||
149 | equal :: c e -> c e -> Bool | ||
diff --git a/lib/Numeric/LinearAlgebra/Tests/Instances.hs b/lib/Numeric/LinearAlgebra/Tests/Instances.hs index 21a6f88..6046ccb 100644 --- a/lib/Numeric/LinearAlgebra/Tests/Instances.hs +++ b/lib/Numeric/LinearAlgebra/Tests/Instances.hs | |||
@@ -26,6 +26,7 @@ module Numeric.LinearAlgebra.Tests.Instances( | |||
26 | FM,ZM, fM,zM | 26 | FM,ZM, fM,zM |
27 | ) where | 27 | ) where |
28 | 28 | ||
29 | import System.Random | ||
29 | 30 | ||
30 | import Numeric.LinearAlgebra | 31 | import Numeric.LinearAlgebra |
31 | import Control.Monad(replicateM) | 32 | import Control.Monad(replicateM) |
@@ -137,7 +138,7 @@ instance (Field a, Arbitrary a, Num (Vector a)) => Arbitrary (Her a) where | |||
137 | 138 | ||
138 | -- a well-conditioned general matrix (the singular values are between 1 and 100) | 139 | -- a well-conditioned general matrix (the singular values are between 1 and 100) |
139 | newtype (WC a) = WC (Matrix a) deriving Show | 140 | newtype (WC a) = WC (Matrix a) deriving Show |
140 | instance (AutoReal a, Field a, Arbitrary a) => Arbitrary (WC a) where | 141 | instance (Convert a, Field a, Arbitrary a, Random (RealOf a)) => Arbitrary (WC a) where |
141 | arbitrary = do | 142 | arbitrary = do |
142 | m <- arbitrary | 143 | m <- arbitrary |
143 | let (u,_,v) = svd m | 144 | let (u,_,v) = svd m |
@@ -146,7 +147,7 @@ instance (AutoReal a, Field a, Arbitrary a) => Arbitrary (WC a) where | |||
146 | n = min r c | 147 | n = min r c |
147 | sv' <- replicateM n (choose (1,100)) | 148 | sv' <- replicateM n (choose (1,100)) |
148 | let s = diagRect (fromList sv') r c | 149 | let s = diagRect (fromList sv') r c |
149 | return $ WC (u <> real'' s <> trans v) | 150 | return $ WC (u <> real s <> trans v) |
150 | 151 | ||
151 | #if MIN_VERSION_QuickCheck(2,0,0) | 152 | #if MIN_VERSION_QuickCheck(2,0,0) |
152 | #else | 153 | #else |
@@ -156,14 +157,14 @@ instance (AutoReal a, Field a, Arbitrary a) => Arbitrary (WC a) where | |||
156 | 157 | ||
157 | -- a well-conditioned square matrix (the singular values are between 1 and 100) | 158 | -- a well-conditioned square matrix (the singular values are between 1 and 100) |
158 | newtype (SqWC a) = SqWC (Matrix a) deriving Show | 159 | newtype (SqWC a) = SqWC (Matrix a) deriving Show |
159 | instance (AutoReal a, Field a, Arbitrary a) => Arbitrary (SqWC a) where | 160 | instance (Convert a, Field a, Arbitrary a, Random (RealOf a)) => Arbitrary (SqWC a) where |
160 | arbitrary = do | 161 | arbitrary = do |
161 | Sq m <- arbitrary | 162 | Sq m <- arbitrary |
162 | let (u,_,v) = svd m | 163 | let (u,_,v) = svd m |
163 | n = rows m | 164 | n = rows m |
164 | sv' <- replicateM n (choose (1,100)) | 165 | sv' <- replicateM n (choose (1,100)) |
165 | let s = diag (fromList sv') | 166 | let s = diag (fromList sv') |
166 | return $ SqWC (u <> real'' s <> trans v) | 167 | return $ SqWC (u <> real s <> trans v) |
167 | 168 | ||
168 | #if MIN_VERSION_QuickCheck(2,0,0) | 169 | #if MIN_VERSION_QuickCheck(2,0,0) |
169 | #else | 170 | #else |
@@ -173,14 +174,15 @@ instance (AutoReal a, Field a, Arbitrary a) => Arbitrary (SqWC a) where | |||
173 | 174 | ||
174 | -- a positive definite square matrix (the eigenvalues are between 0 and 100) | 175 | -- a positive definite square matrix (the eigenvalues are between 0 and 100) |
175 | newtype (PosDef a) = PosDef (Matrix a) deriving Show | 176 | newtype (PosDef a) = PosDef (Matrix a) deriving Show |
176 | instance (AutoReal a, Field a, Arbitrary a, Num (Vector a)) => Arbitrary (PosDef a) where | 177 | instance (Convert a, Field a, Arbitrary a, Num (Vector a), Random (RealOf a)) |
178 | => Arbitrary (PosDef a) where | ||
177 | arbitrary = do | 179 | arbitrary = do |
178 | Her m <- arbitrary | 180 | Her m <- arbitrary |
179 | let (_,v) = eigSH m | 181 | let (_,v) = eigSH m |
180 | n = rows m | 182 | n = rows m |
181 | l <- replicateM n (choose (0,100)) | 183 | l <- replicateM n (choose (0,100)) |
182 | let s = diag (fromList l) | 184 | let s = diag (fromList l) |
183 | p = v <> real'' s <> ctrans v | 185 | p = v <> real s <> ctrans v |
184 | return $ PosDef (0.5 * p + 0.5 * ctrans p) | 186 | return $ PosDef (0.5 * p + 0.5 * ctrans p) |
185 | 187 | ||
186 | #if MIN_VERSION_QuickCheck(2,0,0) | 188 | #if MIN_VERSION_QuickCheck(2,0,0) |
diff --git a/lib/Numeric/LinearAlgebra/Tests/Properties.hs b/lib/Numeric/LinearAlgebra/Tests/Properties.hs index d312e52..b96f53e 100644 --- a/lib/Numeric/LinearAlgebra/Tests/Properties.hs +++ b/lib/Numeric/LinearAlgebra/Tests/Properties.hs | |||
@@ -42,14 +42,14 @@ module Numeric.LinearAlgebra.Tests.Properties ( | |||
42 | linearSolveProp, linearSolveProp2 | 42 | linearSolveProp, linearSolveProp2 |
43 | ) where | 43 | ) where |
44 | 44 | ||
45 | import Numeric.LinearAlgebra hiding (real,complex) | 45 | import Numeric.LinearAlgebra --hiding (real,complex) |
46 | import Numeric.LinearAlgebra.LAPACK | 46 | import Numeric.LinearAlgebra.LAPACK |
47 | import Debug.Trace | 47 | import Debug.Trace |
48 | #include "quickCheckCompat.h" | 48 | #include "quickCheckCompat.h" |
49 | 49 | ||
50 | 50 | ||
51 | real x = real'' x | 51 | --real x = real'' x |
52 | complex x = complex'' x | 52 | --complex x = complex'' x |
53 | 53 | ||
54 | debug x = trace (show x) x | 54 | debug x = trace (show x) x |
55 | 55 | ||