summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/LinearAlgebra.hs
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra.hs')
-rw-r--r--packages/base/src/Numeric/LinearAlgebra.hs251
1 files changed, 242 insertions, 9 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra.hs b/packages/base/src/Numeric/LinearAlgebra.hs
index ad315e4..6a9c33a 100644
--- a/packages/base/src/Numeric/LinearAlgebra.hs
+++ b/packages/base/src/Numeric/LinearAlgebra.hs
@@ -1,22 +1,255 @@
1-------------------------------------------------------------------------------- 1{-# LANGUAGE FlexibleContexts #-}
2
3-----------------------------------------------------------------------------
2{- | 4{- |
3Module : Numeric.LinearAlgebra 5Module : Numeric.LinearAlgebra
4Copyright : (c) Alberto Ruiz 2006-14 6Copyright : (c) Alberto Ruiz 2006-15
5License : BSD3 7License : BSD3
6Maintainer : Alberto Ruiz 8Maintainer : Alberto Ruiz
7Stability : provisional 9Stability : provisional
8 10
9-}
10--------------------------------------------------------------------------------
11{-# OPTIONS_HADDOCK hide #-}
12 11
12-}
13-----------------------------------------------------------------------------
13module Numeric.LinearAlgebra ( 14module Numeric.LinearAlgebra (
14 module Numeric.Container, 15
15 module Numeric.LinearAlgebra.Algorithms 16 -- * Basic types and data manipulation
17 -- | This package works with 2D ('Matrix') and 1D ('Vector')
18 -- arrays of real ('R') or complex ('C') double precision numbers.
19 -- Single precision and machine integers are also supported for
20 -- basic arithmetic and data manipulation.
21 module Numeric.LinearAlgebra.Data,
22
23 -- * Numeric classes
24 -- |
25 -- The standard numeric classes are defined elementwise:
26 --
27 -- >>> vector [1,2,3] * vector [3,0,-2]
28 -- fromList [3.0,0.0,-6.0]
29 --
30 -- >>> matrix 3 [1..9] * ident 3
31 -- (3><3)
32 -- [ 1.0, 0.0, 0.0
33 -- , 0.0, 5.0, 0.0
34 -- , 0.0, 0.0, 9.0 ]
35
36 -- * Autoconformable dimensions
37 -- |
38 -- In most operations, single-element vectors and matrices
39 -- (created from numeric literals or using 'scalar'), and matrices
40 -- with just one row or column, automatically
41 -- expand to match the dimensions of the other operand:
42 --
43 -- >>> 5 + 2*ident 3 :: Matrix Double
44 -- (3><3)
45 -- [ 7.0, 5.0, 5.0
46 -- , 5.0, 7.0, 5.0
47 -- , 5.0, 5.0, 7.0 ]
48 --
49 -- >>> (4><3) [1..] + row [10,20,30]
50 -- (4><3)
51 -- [ 11.0, 22.0, 33.0
52 -- , 14.0, 25.0, 36.0
53 -- , 17.0, 28.0, 39.0
54 -- , 20.0, 31.0, 42.0 ]
55 --
56
57 -- * Products
58 -- ** Dot
59 dot, (<.>),
60 -- ** Matrix-vector
61 (#>), (<#), (!#>),
62 -- ** Matrix-matrix
63 (<>),
64 -- | The matrix product is also implemented in the "Data.Monoid" instance, where
65 -- single-element matrices (created from numeric literals or using 'scalar')
66 -- are used for scaling.
67 --
68 -- >>> import Data.Monoid as M
69 -- >>> let m = matrix 3 [1..6]
70 -- >>> m M.<> 2 M.<> diagl[0.5,1,0]
71 -- (2><3)
72 -- [ 1.0, 4.0, 0.0
73 -- , 4.0, 10.0, 0.0 ]
74 --
75 -- 'mconcat' uses 'optimiseMult' to get the optimal association order.
76
77
78 -- ** Other
79 outer, kronecker, cross,
80 scale, add,
81 sumElements, prodElements,
82
83 -- * Linear systems
84 -- ** General
85 (<\>),
86 linearSolveLS,
87 linearSolveSVD,
88 -- ** Determined
89 linearSolve,
90 luSolve, luPacked,
91 luSolve', luPacked',
92 -- ** Symmetric indefinite
93 ldlSolve, ldlPacked,
94 -- ** Positive definite
95 cholSolve,
96 -- ** Sparse
97 cgSolve,
98 cgSolve',
99
100 -- * Inverse and pseudoinverse
101 inv, pinv, pinvTol,
102
103 -- * Determinant and rank
104 rcond, rank,
105 det, invlndet,
106
107 -- * Norms
108 Normed(..),
109 norm_Frob, norm_nuclear,
110
111 -- * Nullspace and range
112 orth,
113 nullspace, null1, null1sym,
114
115 -- * Singular value decomposition
116 svd,
117 thinSVD,
118 compactSVD,
119 singularValues,
120 leftSV, rightSV,
121
122 -- * Eigendecomposition
123 eig, eigSH,
124 eigenvalues, eigenvaluesSH,
125 geigSH,
126
127 -- * QR
128 qr, rq, qrRaw, qrgr,
129
130 -- * Cholesky
131 chol, mbChol,
132
133 -- * LU
134 lu, luFact,
135
136 -- * Hessenberg
137 hess,
138
139 -- * Schur
140 schur,
141
142 -- * Matrix functions
143 expm,
144 sqrtm,
145 matFunc,
146
147 -- * Correlation and convolution
148 corr, conv, corrMin, corr2, conv2,
149
150 -- * Random arrays
151
152 Seed, RandDist(..), randomVector, rand, randn, gaussianSample, uniformSample,
153
154 -- * Misc
155 meanCov, rowOuters, pairwiseD2, unitary, peps, relativeError, magnit,
156 haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv,
157 iC, sym, mTm, trustSym, unSym,
158 -- * Auxiliary classes
159 Element, Container, Product, Numeric, LSDiv, Herm,
160 Complexable, RealElement,
161 RealOf, ComplexOf, SingleOf, DoubleOf,
162 IndexOf,
163 Field, Linear(), Additive(),
164 Transposable,
165 LU(..),
166 LDL(..),
167 QR(..),
168 CGState(..),
169 Testable(..)
16) where 170) where
17 171
18import Numeric.Container 172import Numeric.LinearAlgebra.Data
19import Numeric.LinearAlgebra.Algorithms 173
20import Numeric.Matrix() 174import Numeric.Matrix()
21import Numeric.Vector() 175import Numeric.Vector()
176import Internal.Matrix
177import Internal.Container hiding ((<>))
178import Internal.Numeric hiding (mul)
179import Internal.Algorithms hiding (linearSolve,Normed,orth,luPacked',linearSolve',luSolve',ldlPacked')
180import qualified Internal.Algorithms as A
181import Internal.Util
182import Internal.Random
183import Internal.Sparse((!#>))
184import Internal.CG
185import Internal.Conversion
186
187{- | dense matrix product
188
189>>> let a = (3><5) [1..]
190>>> a
191(3><5)
192 [ 1.0, 2.0, 3.0, 4.0, 5.0
193 , 6.0, 7.0, 8.0, 9.0, 10.0
194 , 11.0, 12.0, 13.0, 14.0, 15.0 ]
195
196>>> let b = (5><2) [1,3, 0,2, -1,5, 7,7, 6,0]
197>>> b
198(5><2)
199 [ 1.0, 3.0
200 , 0.0, 2.0
201 , -1.0, 5.0
202 , 7.0, 7.0
203 , 6.0, 0.0 ]
204
205>>> a <> b
206(3><2)
207 [ 56.0, 50.0
208 , 121.0, 135.0
209 , 186.0, 220.0 ]
210
211-}
212(<>) :: Numeric t => Matrix t -> Matrix t -> Matrix t
213(<>) = mXm
214infixr 8 <>
215
216
217{- | 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'.
218
219@
220a = (2><2)
221 [ 1.0, 2.0
222 , 3.0, 5.0 ]
223@
224
225@
226b = (2><3)
227 [ 6.0, 1.0, 10.0
228 , 15.0, 3.0, 26.0 ]
229@
230
231>>> linearSolve a b
232Just (2><3)
233 [ -1.4802973661668753e-15, 0.9999999999999997, 1.999999999999997
234 , 3.000000000000001, 1.6653345369377348e-16, 4.000000000000002 ]
235
236>>> let Just x = it
237>>> disp 5 x
2382x3
239-0.00000 1.00000 2.00000
240 3.00000 0.00000 4.00000
241
242>>> a <> x
243(2><3)
244 [ 6.0, 1.0, 10.0
245 , 15.0, 3.0, 26.0 ]
246
247-}
248linearSolve m b = A.mbLinearSolve m b
249
250-- | return an orthonormal basis of the null space of a matrix. See also 'nullspaceSVD'.
251nullspace m = nullspaceSVD (Left (1*eps)) m (rightSV m)
252
253-- | return an orthonormal basis of the range space of a matrix. See also 'orthSVD'.
254orth m = orthSVD (Left (1*eps)) m (leftSV m)
22 255