diff options
author | Alberto Ruiz <aruiz@um.es> | 2015-07-16 20:16:59 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2015-07-16 20:16:59 +0200 |
commit | a273fdb74b04db6d57d5c9b15e676d83357e71fd (patch) | |
tree | 99189532f2a37129a7ec3696f681ff3fd3314950 /packages/base/src/Numeric | |
parent | d9c99a670a393fb232641183623a7fa5921ccff2 (diff) |
Her, LU, LDL, Linear, Additive
Diffstat (limited to 'packages/base/src/Numeric')
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra.hs | 47 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/HMatrix.hs | 3 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Static.hs | 12 |
3 files changed, 33 insertions, 29 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra.hs b/packages/base/src/Numeric/LinearAlgebra.hs index 9a924e0..7be2600 100644 --- a/packages/base/src/Numeric/LinearAlgebra.hs +++ b/packages/base/src/Numeric/LinearAlgebra.hs | |||
@@ -53,11 +53,11 @@ module Numeric.LinearAlgebra ( | |||
53 | -- | 53 | -- |
54 | 54 | ||
55 | -- * Products | 55 | -- * Products |
56 | -- ** dot | 56 | -- ** Dot |
57 | dot, (<.>), | 57 | dot, (<.>), |
58 | -- ** matrix-vector | 58 | -- ** Matrix-vector |
59 | (#>), (<#), (!#>), | 59 | (#>), (<#), (!#>), |
60 | -- ** matrix-matrix | 60 | -- ** Matrix-matrix |
61 | (<>), | 61 | (<>), |
62 | -- | The matrix product is also implemented in the "Data.Monoid" instance, where | 62 | -- | The matrix product is also implemented in the "Data.Monoid" instance, where |
63 | -- single-element matrices (created from numeric literals or using 'scalar') | 63 | -- single-element matrices (created from numeric literals or using 'scalar') |
@@ -73,20 +73,25 @@ module Numeric.LinearAlgebra ( | |||
73 | -- 'mconcat' uses 'optimiseMult' to get the optimal association order. | 73 | -- 'mconcat' uses 'optimiseMult' to get the optimal association order. |
74 | 74 | ||
75 | 75 | ||
76 | -- ** other | 76 | -- ** Other |
77 | outer, kronecker, cross, | 77 | outer, kronecker, cross, |
78 | scale, | 78 | scale, add, |
79 | sumElements, prodElements, | 79 | sumElements, prodElements, |
80 | 80 | ||
81 | -- * Linear systems | 81 | -- * Linear systems |
82 | -- ** General | ||
82 | (<\>), | 83 | (<\>), |
83 | linearSolve, | ||
84 | linearSolveLS, | 84 | linearSolveLS, |
85 | linearSolveSVD, | 85 | linearSolveSVD, |
86 | luSolve, | 86 | -- ** Determined |
87 | luSolve', | 87 | linearSolve, |
88 | luSolve, luPacked, | ||
89 | luSolve', luPacked', | ||
90 | -- ** Symmetric indefinite | ||
91 | ldlSolve, ldlPacked, | ||
92 | -- ** Positive definite | ||
88 | cholSolve, | 93 | cholSolve, |
89 | ldlSolve, | 94 | -- ** Sparse |
90 | cgSolve, | 95 | cgSolve, |
91 | cgSolve', | 96 | cgSolve', |
92 | 97 | ||
@@ -113,21 +118,18 @@ module Numeric.LinearAlgebra ( | |||
113 | leftSV, rightSV, | 118 | leftSV, rightSV, |
114 | 119 | ||
115 | -- * Eigendecomposition | 120 | -- * Eigendecomposition |
116 | eig, eigSH, eigSH', | 121 | eig, eigSH, |
117 | eigenvalues, eigenvaluesSH, eigenvaluesSH', | 122 | eigenvalues, eigenvaluesSH, |
118 | geigSH', | 123 | geigSH, |
119 | 124 | ||
120 | -- * QR | 125 | -- * QR |
121 | qr, rq, qrRaw, qrgr, | 126 | qr, rq, qrRaw, qrgr, |
122 | 127 | ||
123 | -- * Cholesky | 128 | -- * Cholesky |
124 | chol, cholSH, mbCholSH, | 129 | chol, mbChol, |
125 | 130 | ||
126 | -- * LU | 131 | -- * LU |
127 | lu, luPacked, luPacked', luFact, | 132 | lu, luFact, |
128 | |||
129 | -- * LDL | ||
130 | ldlPacked, ldlPackedSH, | ||
131 | 133 | ||
132 | -- * Hessenberg | 134 | -- * Hessenberg |
133 | hess, | 135 | hess, |
@@ -150,14 +152,16 @@ module Numeric.LinearAlgebra ( | |||
150 | -- * Misc | 152 | -- * Misc |
151 | meanCov, rowOuters, pairwiseD2, unitary, peps, relativeError, magnit, | 153 | meanCov, rowOuters, pairwiseD2, unitary, peps, relativeError, magnit, |
152 | haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv, | 154 | haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv, |
153 | iC, | 155 | iC, sym, xTx, trustSym, her, |
154 | -- * Auxiliary classes | 156 | -- * Auxiliary classes |
155 | Element, Container, Product, Numeric, LSDiv, | 157 | Element, Container, Product, Numeric, LSDiv, Her, |
156 | Complexable, RealElement, | 158 | Complexable, RealElement, |
157 | RealOf, ComplexOf, SingleOf, DoubleOf, | 159 | RealOf, ComplexOf, SingleOf, DoubleOf, |
158 | IndexOf, | 160 | IndexOf, |
159 | Field, | 161 | Field, Linear(), Additive(), |
160 | Transposable, | 162 | Transposable, |
163 | LU(..), | ||
164 | LDL(..), | ||
161 | CGState(..), | 165 | CGState(..), |
162 | Testable(..) | 166 | Testable(..) |
163 | ) where | 167 | ) where |
@@ -169,7 +173,7 @@ import Numeric.Vector() | |||
169 | import Internal.Matrix | 173 | import Internal.Matrix |
170 | import Internal.Container hiding ((<>)) | 174 | import Internal.Container hiding ((<>)) |
171 | import Internal.Numeric hiding (mul) | 175 | import Internal.Numeric hiding (mul) |
172 | import Internal.Algorithms hiding (linearSolve,Normed,orth,luPacked',linearSolve',luSolve') | 176 | import Internal.Algorithms hiding (linearSolve,Normed,orth,luPacked',linearSolve',luSolve',ldlPacked') |
173 | import qualified Internal.Algorithms as A | 177 | import qualified Internal.Algorithms as A |
174 | import Internal.Util | 178 | import Internal.Util |
175 | import Internal.Random | 179 | import Internal.Random |
@@ -246,4 +250,3 @@ nullspace m = nullspaceSVD (Left (1*eps)) m (rightSV m) | |||
246 | -- | return an orthonormal basis of the range space of a matrix. See also 'orthSVD'. | 250 | -- | return an orthonormal basis of the range space of a matrix. See also 'orthSVD'. |
247 | orth m = orthSVD (Left (1*eps)) m (leftSV m) | 251 | orth m = orthSVD (Left (1*eps)) m (leftSV m) |
248 | 252 | ||
249 | |||
diff --git a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs index bac1c0c..5ce529c 100644 --- a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs +++ b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs | |||
@@ -13,11 +13,12 @@ compatibility with previous version, to be removed | |||
13 | 13 | ||
14 | module Numeric.LinearAlgebra.HMatrix ( | 14 | module Numeric.LinearAlgebra.HMatrix ( |
15 | module Numeric.LinearAlgebra, | 15 | module Numeric.LinearAlgebra, |
16 | (¦),(——),ℝ,ℂ,(<·>),app,mul | 16 | (¦),(——),ℝ,ℂ,(<·>),app,mul, cholSH, mbCholSH, eigSH', eigenvaluesSH', geigSH' |
17 | ) where | 17 | ) where |
18 | 18 | ||
19 | import Numeric.LinearAlgebra | 19 | import Numeric.LinearAlgebra |
20 | import Internal.Util | 20 | import Internal.Util |
21 | import Internal.Algorithms(cholSH, mbCholSH, eigSH', eigenvaluesSH', geigSH') | ||
21 | 22 | ||
22 | infixr 8 <·> | 23 | infixr 8 <·> |
23 | (<·>) :: Numeric t => Vector t -> Vector t -> t | 24 | (<·>) :: Numeric t => Vector t -> Vector t -> t |
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs index 0dab0e6..ded69fa 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs | |||
@@ -63,9 +63,9 @@ import GHC.TypeLits | |||
63 | import Numeric.LinearAlgebra hiding ( | 63 | import Numeric.LinearAlgebra hiding ( |
64 | (<>),(#>),(<.>),Konst(..),diag, disp,(===),(|||), | 64 | (<>),(#>),(<.>),Konst(..),diag, disp,(===),(|||), |
65 | row,col,vector,matrix,linspace,toRows,toColumns, | 65 | row,col,vector,matrix,linspace,toRows,toColumns, |
66 | (<\>),fromList,takeDiag,svd,eig,eigSH,eigSH', | 66 | (<\>),fromList,takeDiag,svd,eig,eigSH, |
67 | eigenvalues,eigenvaluesSH,eigenvaluesSH',build, | 67 | eigenvalues,eigenvaluesSH,build, |
68 | qr,size,dot,chol,range,R,C) | 68 | qr,size,dot,chol,range,R,C,Her,her,sym) |
69 | import qualified Numeric.LinearAlgebra as LA | 69 | import qualified Numeric.LinearAlgebra as LA |
70 | import Data.Proxy(Proxy) | 70 | import Data.Proxy(Proxy) |
71 | import Internal.Static | 71 | import Internal.Static |
@@ -292,10 +292,10 @@ her m = Her $ (m + LA.tr m)/2 | |||
292 | 292 | ||
293 | instance KnownNat n => Eigen (Sym n) (R n) (L n n) | 293 | instance KnownNat n => Eigen (Sym n) (R n) (L n n) |
294 | where | 294 | where |
295 | eigenvalues (Sym (extract -> m)) = mkR . LA.eigenvaluesSH' $ m | 295 | eigenvalues (Sym (extract -> m)) = mkR . LA.eigenvaluesSH . LA.trustSym $ m |
296 | eigensystem (Sym (extract -> m)) = (mkR l, mkL v) | 296 | eigensystem (Sym (extract -> m)) = (mkR l, mkL v) |
297 | where | 297 | where |
298 | (l,v) = LA.eigSH' m | 298 | (l,v) = LA.eigSH . LA.trustSym $ m |
299 | 299 | ||
300 | instance KnownNat n => Eigen (Sq n) (C n) (M n n) | 300 | instance KnownNat n => Eigen (Sq n) (C n) (M n n) |
301 | where | 301 | where |
@@ -305,7 +305,7 @@ instance KnownNat n => Eigen (Sq n) (C n) (M n n) | |||
305 | (l,v) = LA.eig m | 305 | (l,v) = LA.eig m |
306 | 306 | ||
307 | chol :: KnownNat n => Sym n -> Sq n | 307 | chol :: KnownNat n => Sym n -> Sq n |
308 | chol (extract . unSym -> m) = mkL $ LA.cholSH m | 308 | chol (extract . unSym -> m) = mkL $ LA.chol $ LA.trustSym m |
309 | 309 | ||
310 | -------------------------------------------------------------------------------- | 310 | -------------------------------------------------------------------------------- |
311 | 311 | ||