diff options
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra')
5 files changed, 10 insertions, 303 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs index a640351..8e67eb4 100644 --- a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs +++ b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | ----------------------------------------------------------------------------- | 1 | -------------------------------------------------------------------------------- |
2 | {- | | 2 | {- | |
3 | Module : Numeric.LinearAlgebra.HMatrix | 3 | Module : Numeric.LinearAlgebra.HMatrix |
4 | Copyright : (c) Alberto Ruiz 2006-14 | 4 | Copyright : (c) Alberto Ruiz 2006-14 |
@@ -7,229 +7,11 @@ Maintainer : Alberto Ruiz | |||
7 | Stability : provisional | 7 | Stability : provisional |
8 | 8 | ||
9 | -} | 9 | -} |
10 | ----------------------------------------------------------------------------- | 10 | -------------------------------------------------------------------------------- |
11 | module Numeric.LinearAlgebra.HMatrix ( | ||
12 | |||
13 | -- * Basic types and data processing | ||
14 | module Numeric.LinearAlgebra.Data, | ||
15 | |||
16 | -- * Arithmetic and numeric classes | ||
17 | -- | | ||
18 | -- The standard numeric classes are defined elementwise: | ||
19 | -- | ||
20 | -- >>> vector [1,2,3] * vector [3,0,-2] | ||
21 | -- fromList [3.0,0.0,-6.0] | ||
22 | -- | ||
23 | -- >>> matrix 3 [1..9] * ident 3 | ||
24 | -- (3><3) | ||
25 | -- [ 1.0, 0.0, 0.0 | ||
26 | -- , 0.0, 5.0, 0.0 | ||
27 | -- , 0.0, 0.0, 9.0 ] | ||
28 | -- | ||
29 | -- In arithmetic operations single-element vectors and matrices | ||
30 | -- (created from numeric literals or using 'scalar') automatically | ||
31 | -- expand to match the dimensions of the other operand: | ||
32 | -- | ||
33 | -- >>> 5 + 2*ident 3 :: Matrix Double | ||
34 | -- (3><3) | ||
35 | -- [ 7.0, 5.0, 5.0 | ||
36 | -- , 5.0, 7.0, 5.0 | ||
37 | -- , 5.0, 5.0, 7.0 ] | ||
38 | -- | ||
39 | -- >>> matrix 3 [1..9] + matrix 1 [10,20,30] | ||
40 | -- (3><3) | ||
41 | -- [ 11.0, 12.0, 13.0 | ||
42 | -- , 24.0, 25.0, 26.0 | ||
43 | -- , 37.0, 38.0, 39.0 ] | ||
44 | -- | ||
45 | |||
46 | -- * Products | ||
47 | -- ** dot | ||
48 | dot, (<·>), | ||
49 | -- ** matrix-vector | ||
50 | app, (#>), (<#), (!#>), | ||
51 | -- ** matrix-matrix | ||
52 | mul, (<>), | ||
53 | -- | The matrix product is also implemented in the "Data.Monoid" instance, where | ||
54 | -- single-element matrices (created from numeric literals or using 'scalar') | ||
55 | -- are used for scaling. | ||
56 | -- | ||
57 | -- >>> import Data.Monoid as M | ||
58 | -- >>> let m = matrix 3 [1..6] | ||
59 | -- >>> m M.<> 2 M.<> diagl[0.5,1,0] | ||
60 | -- (2><3) | ||
61 | -- [ 1.0, 4.0, 0.0 | ||
62 | -- , 4.0, 10.0, 0.0 ] | ||
63 | -- | ||
64 | -- 'mconcat' uses 'optimiseMult' to get the optimal association order. | ||
65 | |||
66 | |||
67 | -- ** other | ||
68 | outer, kronecker, cross, | ||
69 | scale, | ||
70 | sumElements, prodElements, | ||
71 | |||
72 | -- * Linear Systems | ||
73 | (<\>), | ||
74 | linearSolve, | ||
75 | linearSolveLS, | ||
76 | linearSolveSVD, | ||
77 | luSolve, | ||
78 | cholSolve, | ||
79 | cgSolve, | ||
80 | cgSolve', | ||
81 | |||
82 | -- * Inverse and pseudoinverse | ||
83 | inv, pinv, pinvTol, | ||
84 | |||
85 | -- * Determinant and rank | ||
86 | rcond, rank, | ||
87 | det, invlndet, | ||
88 | |||
89 | -- * Norms | ||
90 | Normed(..), | ||
91 | norm_Frob, norm_nuclear, | ||
92 | |||
93 | -- * Nullspace and range | ||
94 | orth, | ||
95 | nullspace, null1, null1sym, | ||
96 | |||
97 | -- * SVD | ||
98 | svd, | ||
99 | thinSVD, | ||
100 | compactSVD, | ||
101 | singularValues, | ||
102 | leftSV, rightSV, | ||
103 | |||
104 | -- * Eigensystems | ||
105 | eig, eigSH, eigSH', | ||
106 | eigenvalues, eigenvaluesSH, eigenvaluesSH', | ||
107 | geigSH', | ||
108 | |||
109 | -- * QR | ||
110 | qr, rq, qrRaw, qrgr, | ||
111 | |||
112 | -- * Cholesky | ||
113 | chol, cholSH, mbCholSH, | ||
114 | |||
115 | -- * Hessenberg | ||
116 | hess, | ||
117 | |||
118 | -- * Schur | ||
119 | schur, | ||
120 | |||
121 | -- * LU | ||
122 | lu, luPacked, | ||
123 | |||
124 | -- * Matrix functions | ||
125 | expm, | ||
126 | sqrtm, | ||
127 | matFunc, | ||
128 | |||
129 | -- * Correlation and convolution | ||
130 | corr, conv, corrMin, corr2, conv2, | ||
131 | |||
132 | -- * Random arrays | ||
133 | 11 | ||
134 | Seed, RandDist(..), randomVector, rand, randn, gaussianSample, uniformSample, | 12 | module Numeric.LinearAlgebra.HMatrix ( |
135 | 13 | module Numeric.LinearAlgebra | |
136 | -- * Misc | ||
137 | meanCov, rowOuters, peps, relativeError, haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv, | ||
138 | ℝ,ℂ,iC, | ||
139 | -- * Auxiliary classes | ||
140 | Element, Container, Product, Numeric, LSDiv, | ||
141 | Complexable, RealElement, | ||
142 | RealOf, ComplexOf, SingleOf, DoubleOf, | ||
143 | IndexOf, | ||
144 | Field, | ||
145 | -- Normed, | ||
146 | Transposable, | ||
147 | CGState(..), | ||
148 | Testable(..) | ||
149 | ) where | 14 | ) where |
150 | 15 | ||
151 | import Numeric.LinearAlgebra.Data | 16 | import Numeric.LinearAlgebra |
152 | |||
153 | import Numeric.Matrix() | ||
154 | import Numeric.Vector() | ||
155 | import Data.Packed.Numeric hiding ((<>), mul) | ||
156 | import Numeric.LinearAlgebra.Algorithms hiding (linearSolve,Normed,orth) | ||
157 | import qualified Numeric.LinearAlgebra.Algorithms as A | ||
158 | import Numeric.LinearAlgebra.Util | ||
159 | import Numeric.LinearAlgebra.Random | ||
160 | import Numeric.Sparse((!#>)) | ||
161 | import Numeric.LinearAlgebra.Util.CG | ||
162 | |||
163 | {- | infix synonym of 'mul' | ||
164 | |||
165 | >>> let a = (3><5) [1..] | ||
166 | >>> a | ||
167 | (3><5) | ||
168 | [ 1.0, 2.0, 3.0, 4.0, 5.0 | ||
169 | , 6.0, 7.0, 8.0, 9.0, 10.0 | ||
170 | , 11.0, 12.0, 13.0, 14.0, 15.0 ] | ||
171 | |||
172 | >>> let b = (5><2) [1,3, 0,2, -1,5, 7,7, 6,0] | ||
173 | >>> b | ||
174 | (5><2) | ||
175 | [ 1.0, 3.0 | ||
176 | , 0.0, 2.0 | ||
177 | , -1.0, 5.0 | ||
178 | , 7.0, 7.0 | ||
179 | , 6.0, 0.0 ] | ||
180 | |||
181 | >>> a <> b | ||
182 | (3><2) | ||
183 | [ 56.0, 50.0 | ||
184 | , 121.0, 135.0 | ||
185 | , 186.0, 220.0 ] | ||
186 | |||
187 | -} | ||
188 | (<>) :: Numeric t => Matrix t -> Matrix t -> Matrix t | ||
189 | (<>) = mXm | ||
190 | infixr 8 <> | ||
191 | |||
192 | -- | dense matrix product | ||
193 | mul :: Numeric t => Matrix t -> Matrix t -> Matrix t | ||
194 | mul = mXm | ||
195 | |||
196 | |||
197 | {- | Solve a linear system (for square coefficient matrix and several right-hand sides) using the LU decomposition, returning Nothing for a singular system. For underconstrained or overconstrained systems use 'linearSolveLS' or 'linearSolveSVD'. | ||
198 | |||
199 | @ | ||
200 | a = (2><2) | ||
201 | [ 1.0, 2.0 | ||
202 | , 3.0, 5.0 ] | ||
203 | @ | ||
204 | |||
205 | @ | ||
206 | b = (2><3) | ||
207 | [ 6.0, 1.0, 10.0 | ||
208 | , 15.0, 3.0, 26.0 ] | ||
209 | @ | ||
210 | |||
211 | >>> linearSolve a b | ||
212 | Just (2><3) | ||
213 | [ -1.4802973661668753e-15, 0.9999999999999997, 1.999999999999997 | ||
214 | , 3.000000000000001, 1.6653345369377348e-16, 4.000000000000002 ] | ||
215 | |||
216 | >>> let Just x = it | ||
217 | >>> disp 5 x | ||
218 | 2x3 | ||
219 | -0.00000 1.00000 2.00000 | ||
220 | 3.00000 0.00000 4.00000 | ||
221 | |||
222 | >>> a <> x | ||
223 | (2><3) | ||
224 | [ 6.0, 1.0, 10.0 | ||
225 | , 15.0, 3.0, 26.0 ] | ||
226 | |||
227 | -} | ||
228 | linearSolve m b = A.mbLinearSolve m b | ||
229 | |||
230 | -- | return an orthonormal basis of the null space of a matrix. See also 'nullspaceSVD'. | ||
231 | nullspace m = nullspaceSVD (Left (1*eps)) m (rightSV m) | ||
232 | |||
233 | -- | return an orthonormal basis of the range space of a matrix. See also 'orthSVD'. | ||
234 | orth m = orthSVD (Left (1*eps)) m (leftSV m) | ||
235 | 17 | ||
diff --git a/packages/base/src/Numeric/LinearAlgebra/HMatrix/Util.hs b/packages/base/src/Numeric/LinearAlgebra/HMatrix/Util.hs deleted file mode 100644 index 818b226..0000000 --- a/packages/base/src/Numeric/LinearAlgebra/HMatrix/Util.hs +++ /dev/null | |||
@@ -1,29 +0,0 @@ | |||
1 | ----------------------------------------------------------------------------- | ||
2 | {- | | ||
3 | Module : Numeric.LinearAlgebra.HMatrix.Util | ||
4 | Copyright : (c) Alberto Ruiz 2015 | ||
5 | License : BSD3 | ||
6 | Maintainer : Alberto Ruiz | ||
7 | Stability : provisional | ||
8 | |||
9 | -} | ||
10 | ----------------------------------------------------------------------------- | ||
11 | |||
12 | module Numeric.LinearAlgebra.HMatrix.Util( | ||
13 | unitary, | ||
14 | pairwiseD2, | ||
15 | -- * Tools for the Kronecker product | ||
16 | -- | ||
17 | -- | (see A. Fusiello, A matter of notation: Several uses of the Kronecker product in | ||
18 | -- 3d computer vision, Pattern Recognition Letters 28 (15) (2007) 2127-2132) | ||
19 | |||
20 | -- | ||
21 | -- | @`vec` (a \<> x \<> b) == ('trans' b ` 'kronecker' ` a) \<> 'vec' x@ | ||
22 | vec, | ||
23 | vech, | ||
24 | dup, | ||
25 | vtrans | ||
26 | ) where | ||
27 | |||
28 | import Numeric.LinearAlgebra.Util | ||
29 | |||
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs index 4c3186f..25b10b4 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs | |||
@@ -60,13 +60,13 @@ module Numeric.LinearAlgebra.Static( | |||
60 | 60 | ||
61 | 61 | ||
62 | import GHC.TypeLits | 62 | import GHC.TypeLits |
63 | import Numeric.LinearAlgebra.HMatrix 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,eigSH', |
67 | eigenvalues,eigenvaluesSH,eigenvaluesSH',build, | 67 | eigenvalues,eigenvaluesSH,eigenvaluesSH',build, |
68 | qr,size,app,mul,dot,chol) | 68 | qr,size,app,mul,dot,chol) |
69 | import qualified Numeric.LinearAlgebra.HMatrix as LA | 69 | import qualified Numeric.LinearAlgebra as LA |
70 | import Data.Proxy(Proxy) | 70 | import Data.Proxy(Proxy) |
71 | import Numeric.LinearAlgebra.Static.Internal | 71 | import Numeric.LinearAlgebra.Static.Internal |
72 | import Control.Arrow((***)) | 72 | import Control.Arrow((***)) |
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs index ec02cf6..a5fc29b 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs | |||
@@ -24,8 +24,8 @@ module Numeric.LinearAlgebra.Static.Internal where | |||
24 | 24 | ||
25 | 25 | ||
26 | import GHC.TypeLits | 26 | import GHC.TypeLits |
27 | import qualified Numeric.LinearAlgebra.HMatrix as LA | 27 | import qualified Numeric.LinearAlgebra as LA |
28 | import Numeric.LinearAlgebra.HMatrix hiding (konst,size) | 28 | import Numeric.LinearAlgebra hiding (konst,size) |
29 | import Data.Packed as D | 29 | import Data.Packed as D |
30 | import Data.Packed.ST | 30 | import Data.Packed.ST |
31 | import Data.Proxy(Proxy) | 31 | import Data.Proxy(Proxy) |
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs index 89202d3..370ca27 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Util.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs | |||
@@ -16,7 +16,6 @@ Stability : provisional | |||
16 | 16 | ||
17 | -} | 17 | -} |
18 | ----------------------------------------------------------------------------- | 18 | ----------------------------------------------------------------------------- |
19 | {-# OPTIONS_HADDOCK hide #-} | ||
20 | 19 | ||
21 | module Numeric.LinearAlgebra.Util( | 20 | module Numeric.LinearAlgebra.Util( |
22 | 21 | ||
@@ -53,18 +52,7 @@ module Numeric.LinearAlgebra.Util( | |||
53 | -- ** 1D | 52 | -- ** 1D |
54 | corr, conv, corrMin, | 53 | corr, conv, corrMin, |
55 | -- ** 2D | 54 | -- ** 2D |
56 | corr2, conv2, separable, | 55 | corr2, conv2, separable |
57 | -- * Tools for the Kronecker product | ||
58 | -- | ||
59 | -- | (see A. Fusiello, A matter of notation: Several uses of the Kronecker product in | ||
60 | -- 3d computer vision, Pattern Recognition Letters 28 (15) (2007) 2127-2132) | ||
61 | |||
62 | -- | ||
63 | -- | @`vec` (a \<> x \<> b) == ('trans' b ` 'kronecker' ` a) \<> 'vec' x@ | ||
64 | vec, | ||
65 | vech, | ||
66 | dup, | ||
67 | vtrans | ||
68 | ) where | 56 | ) where |
69 | 57 | ||
70 | import Data.Packed.Numeric | 58 | import Data.Packed.Numeric |
@@ -407,40 +395,6 @@ null1sym = last . toColumns . snd . eigSH' | |||
407 | 395 | ||
408 | -------------------------------------------------------------------------------- | 396 | -------------------------------------------------------------------------------- |
409 | 397 | ||
410 | vec :: Element t => Matrix t -> Vector t | ||
411 | -- ^ stacking of columns | ||
412 | vec = flatten . trans | ||
413 | |||
414 | |||
415 | vech :: Element t => Matrix t -> Vector t | ||
416 | -- ^ half-vectorization (of the lower triangular part) | ||
417 | vech m = vjoin . zipWith f [0..] . toColumns $ m | ||
418 | where | ||
419 | f k v = subVector k (dim v - k) v | ||
420 | |||
421 | |||
422 | dup :: (Num t, Num (Vector t), Element t) => Int -> Matrix t | ||
423 | -- ^ duplication matrix (@'dup' k \<> 'vech' m == 'vec' m@, for symmetric m of 'dim' k) | ||
424 | dup k = trans $ fromRows $ map f es | ||
425 | where | ||
426 | rs = zip [0..] (toRows (ident (k^(2::Int)))) | ||
427 | es = [(i,j) | j <- [0..k-1], i <- [0..k-1], i>=j ] | ||
428 | f (i,j) | i == j = g (k*j + i) | ||
429 | | otherwise = g (k*j + i) + g (k*i + j) | ||
430 | g j = v | ||
431 | where | ||
432 | Just v = lookup j rs | ||
433 | |||
434 | |||
435 | vtrans :: Element t => Int -> Matrix t -> Matrix t | ||
436 | -- ^ generalized \"vector\" transposition: @'vtrans' 1 == 'trans'@, and @'vtrans' ('rows' m) m == 'asColumn' ('vec' m)@ | ||
437 | vtrans p m | r == 0 = fromBlocks . map (map asColumn . takesV (replicate q p)) . toColumns $ m | ||
438 | | otherwise = error $ "vtrans " ++ show p ++ " of matrix with " ++ show (rows m) ++ " rows" | ||
439 | where | ||
440 | (q,r) = divMod (rows m) p | ||
441 | |||
442 | -------------------------------------------------------------------------------- | ||
443 | |||
444 | infixl 0 ~!~ | 398 | infixl 0 ~!~ |
445 | c ~!~ msg = when c (error msg) | 399 | c ~!~ msg = when c (error msg) |
446 | 400 | ||