diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-06-07 11:44:13 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-06-07 11:44:13 +0200 |
commit | 907d69558f8819a44b552e820750f99340f1f107 (patch) | |
tree | f825b16bf85ae4496b0eaca94ed239f2845c466d | |
parent | 2e07762524d0d08fbc2e565529d480dc7fa479b5 (diff) |
documentation
-rw-r--r-- | packages/base/src/Data/Packed/Numeric.hs | 74 | ||||
-rw-r--r-- | packages/base/src/Numeric/HMatrix.hs | 83 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Util.hs | 11 | ||||
-rw-r--r-- | packages/base/src/Numeric/Sparse.hs | 29 |
4 files changed, 115 insertions, 82 deletions
diff --git a/packages/base/src/Data/Packed/Numeric.hs b/packages/base/src/Data/Packed/Numeric.hs index e90c612..d2a20be 100644 --- a/packages/base/src/Data/Packed/Numeric.hs +++ b/packages/base/src/Data/Packed/Numeric.hs | |||
@@ -1,4 +1,3 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | 1 | {-# LANGUAGE FlexibleContexts #-} |
3 | {-# LANGUAGE FlexibleInstances #-} | 2 | {-# LANGUAGE FlexibleInstances #-} |
4 | {-# LANGUAGE MultiParamTypeClasses #-} | 3 | {-# LANGUAGE MultiParamTypeClasses #-} |
@@ -95,67 +94,46 @@ linspace 1 (a,b) = fromList[(a+b)/2] | |||
95 | linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1] | 94 | linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1] |
96 | where s = (b-a)/fromIntegral (n-1) | 95 | where s = (b-a)/fromIntegral (n-1) |
97 | 96 | ||
98 | -------------------------------------------------------- | 97 | -------------------------------------------------------------------------------- |
99 | |||
100 | {- Matrix product, matrix - vector product, and dot product (equivalent to 'contraction') | ||
101 | |||
102 | (This operator can also be written using the unicode symbol ◇ (25c7).) | ||
103 | |||
104 | Examples: | ||
105 | |||
106 | >>> let a = (3><4) [1..] :: Matrix Double | ||
107 | >>> let v = fromList [1,0,2,-1] :: Vector Double | ||
108 | >>> let u = fromList [1,2,3] :: Vector Double | ||
109 | |||
110 | >>> a | ||
111 | (3><4) | ||
112 | [ 1.0, 2.0, 3.0, 4.0 | ||
113 | , 5.0, 6.0, 7.0, 8.0 | ||
114 | , 9.0, 10.0, 11.0, 12.0 ] | ||
115 | |||
116 | matrix × matrix: | ||
117 | 98 | ||
118 | >>> disp 2 (a <.> trans a) | 99 | infixl 7 <.> |
119 | 3x3 | 100 | -- | An infix synonym for 'dot' |
120 | 30 70 110 | 101 | (<.>) :: Numeric t => Vector t -> Vector t -> t |
121 | 70 174 278 | 102 | (<.>) = dot |
122 | 110 278 446 | ||
123 | 103 | ||
124 | matrix × vector: | ||
125 | 104 | ||
126 | >>> a <.> v | 105 | infixr 8 <·>, #> |
127 | fromList [3.0,11.0,19.0] | ||
128 | 106 | ||
129 | dot product: | 107 | {- | dot product |
130 | 108 | ||
131 | >>> u <.> fromList[3,2,1::Double] | 109 | >>> vect [1,2,3,4] <·> vect [-2,0,1,1] |
132 | 10 | 110 | 5.0 |
133 | 111 | ||
134 | For complex vectors the first argument is conjugated: | 112 | >>> let 𝑖 = 0:+1 :: ℂ |
113 | >>> fromList [1+𝑖,1] <·> fromList [1,1+𝑖] | ||
114 | 2.0 :+ 0.0 | ||
135 | 115 | ||
136 | >>> fromList [1,i] <.> fromList[2*i+1,3] | 116 | (the dot symbol "·" is obtained by Alt-Gr .) |
137 | 1.0 :+ (-1.0) | ||
138 | 117 | ||
139 | >>> fromList [1,i,1-i] <.> complex a | ||
140 | fromList [10.0 :+ 4.0,12.0 :+ 4.0,14.0 :+ 4.0,16.0 :+ 4.0] | ||
141 | -} | 118 | -} |
119 | (<·>) :: Numeric t => Vector t -> Vector t -> t | ||
120 | (<·>) = dot | ||
142 | 121 | ||
143 | 122 | ||
144 | -------------------------------------------------------------------------------- | 123 | {- | dense matrix-vector product |
145 | |||
146 | infixl 7 <.> | ||
147 | -- | An infix synonym for 'dot' | ||
148 | (<.>) :: Numeric t => Vector t -> Vector t -> t | ||
149 | (<.>) = dot | ||
150 | 124 | ||
125 | >>> let m = (2><3) [1..] | ||
126 | >>> m | ||
127 | (2><3) | ||
128 | [ 1.0, 2.0, 3.0 | ||
129 | , 4.0, 5.0, 6.0 ] | ||
151 | 130 | ||
152 | infixr 8 <·>, #> | 131 | >>> let v = vect [10,20,30] |
153 | -- | dot product | ||
154 | (<·>) :: Numeric t => Vector t -> Vector t -> t | ||
155 | (<·>) = dot | ||
156 | 132 | ||
133 | >>> m #> v | ||
134 | fromList [140.0,320.0] | ||
157 | 135 | ||
158 | -- | matrix-vector product | 136 | -} |
159 | (#>) :: Numeric t => Matrix t -> Vector t -> Vector t | 137 | (#>) :: Numeric t => Matrix t -> Vector t -> Vector t |
160 | (#>) = mXv | 138 | (#>) = mXv |
161 | 139 | ||
@@ -291,4 +269,4 @@ instance Numeric (Complex Double) | |||
291 | instance Numeric Float | 269 | instance Numeric Float |
292 | instance Numeric (Complex Float) | 270 | instance Numeric (Complex Float) |
293 | 271 | ||
294 | -------------------------------------------------------------------------------- | 272 | |
diff --git a/packages/base/src/Numeric/HMatrix.hs b/packages/base/src/Numeric/HMatrix.hs index 9d34658..ec96bfc 100644 --- a/packages/base/src/Numeric/HMatrix.hs +++ b/packages/base/src/Numeric/HMatrix.hs | |||
@@ -17,10 +17,10 @@ module Numeric.HMatrix ( | |||
17 | -- | | 17 | -- | |
18 | -- The standard numeric classes are defined elementwise: | 18 | -- The standard numeric classes are defined elementwise: |
19 | -- | 19 | -- |
20 | -- >>> fromList [1,2,3] * fromList [3,0,-2 :: Double] | 20 | -- >>> vect [1,2,3] * vect [3,0,-2] |
21 | -- fromList [3.0,0.0,-6.0] | 21 | -- fromList [3.0,0.0,-6.0] |
22 | -- | 22 | -- |
23 | -- >>> (3><3) [1..9] * ident 3 :: Matrix Double | 23 | -- >>> mat 3 [1..9] * ident 3 |
24 | -- (3><3) | 24 | -- (3><3) |
25 | -- [ 1.0, 0.0, 0.0 | 25 | -- [ 1.0, 0.0, 0.0 |
26 | -- , 0.0, 5.0, 0.0 | 26 | -- , 0.0, 5.0, 0.0 |
@@ -36,6 +36,12 @@ module Numeric.HMatrix ( | |||
36 | -- , 5.0, 7.0, 5.0 | 36 | -- , 5.0, 7.0, 5.0 |
37 | -- , 5.0, 5.0, 7.0 ] | 37 | -- , 5.0, 5.0, 7.0 ] |
38 | -- | 38 | -- |
39 | -- >>> mat 3 [1..9] + mat 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 | -- | ||
39 | 45 | ||
40 | -- * Products | 46 | -- * Products |
41 | -- ** dot | 47 | -- ** dot |
@@ -48,11 +54,12 @@ module Numeric.HMatrix ( | |||
48 | -- single-element matrices (created from numeric literals or using 'scalar') | 54 | -- single-element matrices (created from numeric literals or using 'scalar') |
49 | -- are used for scaling. | 55 | -- are used for scaling. |
50 | -- | 56 | -- |
51 | -- >>> let m = (2><3)[1..] :: Matrix Double | 57 | -- >>> import Data.Monoid as M |
52 | -- >>> m <> 2 <> diagl[0.5,1,0] | 58 | -- >>> let m = mat 3 [1..6] |
59 | -- >>> m M.<> 2 M.<> diagl[0.5,1,0] | ||
53 | -- (2><3) | 60 | -- (2><3) |
54 | -- [ 1.0, 4.0, 0.0 | 61 | -- [ 1.0, 4.0, 0.0 |
55 | -- , 4.0, 10.0, 0.0 ] | 62 | -- , 4.0, 10.0, 0.0 ] |
56 | -- | 63 | -- |
57 | -- 'mconcat' uses 'optimiseMult' to get the optimal association order. | 64 | -- 'mconcat' uses 'optimiseMult' to get the optimal association order. |
58 | 65 | ||
@@ -76,10 +83,18 @@ module Numeric.HMatrix ( | |||
76 | inv, pinv, pinvTol, | 83 | inv, pinv, pinvTol, |
77 | 84 | ||
78 | -- * Determinant and rank | 85 | -- * Determinant and rank |
79 | rcond, rank, ranksv, | 86 | rcond, rank, |
80 | det, invlndet, | 87 | det, invlndet, |
81 | 88 | ||
82 | -- * Singular value decomposition | 89 | -- * Norms |
90 | Normed(..), | ||
91 | norm_Frob, norm_nuclear, | ||
92 | |||
93 | -- * Nullspace and range | ||
94 | orth, | ||
95 | nullspace, null1, null1sym, | ||
96 | |||
97 | -- * SVD | ||
83 | svd, | 98 | svd, |
84 | fullSVD, | 99 | fullSVD, |
85 | thinSVD, | 100 | thinSVD, |
@@ -112,18 +127,6 @@ module Numeric.HMatrix ( | |||
112 | sqrtm, | 127 | sqrtm, |
113 | matFunc, | 128 | matFunc, |
114 | 129 | ||
115 | -- * Nullspace | ||
116 | nullspacePrec, | ||
117 | nullVector, | ||
118 | nullspaceSVD, | ||
119 | null1, null1sym, | ||
120 | |||
121 | orth, | ||
122 | |||
123 | -- * Norms | ||
124 | Normed(..), | ||
125 | norm_Frob, norm_nuclear, | ||
126 | |||
127 | -- * Correlation and convolution | 130 | -- * Correlation and convolution |
128 | corr, conv, corrMin, corr2, conv2, | 131 | corr, conv, corrMin, corr2, conv2, |
129 | 132 | ||
@@ -132,7 +135,8 @@ module Numeric.HMatrix ( | |||
132 | Seed, RandDist(..), randomVector, rand, randn, gaussianSample, uniformSample, | 135 | Seed, RandDist(..), randomVector, rand, randn, gaussianSample, uniformSample, |
133 | 136 | ||
134 | -- * Misc | 137 | -- * Misc |
135 | meanCov, peps, relativeError, haussholder, optimiseMult, udot, | 138 | meanCov, peps, relativeError, haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv, |
139 | ℝ,ℂ,iC, | ||
136 | -- * Auxiliary classes | 140 | -- * Auxiliary classes |
137 | Element, Container, Product, Numeric, LSDiv, | 141 | Element, Container, Product, Numeric, LSDiv, |
138 | Complexable, RealElement, | 142 | Complexable, RealElement, |
@@ -142,8 +146,7 @@ module Numeric.HMatrix ( | |||
142 | -- Normed, | 146 | -- Normed, |
143 | Transposable, | 147 | Transposable, |
144 | CGState(..), | 148 | CGState(..), |
145 | Testable(..), | 149 | Testable(..) |
146 | ℕ,ℤ,ℝ,ℂ, i_C | ||
147 | ) where | 150 | ) where |
148 | 151 | ||
149 | import Numeric.LinearAlgebra.Data | 152 | import Numeric.LinearAlgebra.Data |
@@ -151,14 +154,38 @@ import Numeric.LinearAlgebra.Data | |||
151 | import Numeric.Matrix() | 154 | import Numeric.Matrix() |
152 | import Numeric.Vector() | 155 | import Numeric.Vector() |
153 | import Data.Packed.Numeric hiding ((<>)) | 156 | import Data.Packed.Numeric hiding ((<>)) |
154 | import Numeric.LinearAlgebra.Algorithms hiding (linearSolve,Normed) | 157 | import Numeric.LinearAlgebra.Algorithms hiding (linearSolve,Normed,orth) |
155 | import qualified Numeric.LinearAlgebra.Algorithms as A | 158 | import qualified Numeric.LinearAlgebra.Algorithms as A |
156 | import Numeric.LinearAlgebra.Util | 159 | import Numeric.LinearAlgebra.Util |
157 | import Numeric.LinearAlgebra.Random | 160 | import Numeric.LinearAlgebra.Random |
158 | import Numeric.Sparse((!#>)) | 161 | import Numeric.Sparse((!#>)) |
159 | import Numeric.LinearAlgebra.Util.CG | 162 | import Numeric.LinearAlgebra.Util.CG |
160 | 163 | ||
161 | -- | matrix product | 164 | {- | dense matrix product |
165 | |||
166 | >>> let a = (3><5) [1..] | ||
167 | >>> a | ||
168 | (3><5) | ||
169 | [ 1.0, 2.0, 3.0, 4.0, 5.0 | ||
170 | , 6.0, 7.0, 8.0, 9.0, 10.0 | ||
171 | , 11.0, 12.0, 13.0, 14.0, 15.0 ] | ||
172 | |||
173 | >>> let b = (5><2) [1,3, 0,2, -1,5, 7,7, 6,0] | ||
174 | >>> b | ||
175 | (5><2) | ||
176 | [ 1.0, 3.0 | ||
177 | , 0.0, 2.0 | ||
178 | , -1.0, 5.0 | ||
179 | , 7.0, 7.0 | ||
180 | , 6.0, 0.0 ] | ||
181 | |||
182 | >>> a <> b | ||
183 | (3><2) | ||
184 | [ 56.0, 50.0 | ||
185 | , 121.0, 135.0 | ||
186 | , 186.0, 220.0 ] | ||
187 | |||
188 | -} | ||
162 | (<>) :: Numeric t => Matrix t -> Matrix t -> Matrix t | 189 | (<>) :: Numeric t => Matrix t -> Matrix t -> Matrix t |
163 | (<>) = mXm | 190 | (<>) = mXm |
164 | infixr 8 <> | 191 | infixr 8 <> |
@@ -166,3 +193,9 @@ infixr 8 <> | |||
166 | -- | 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'. | 193 | -- | 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'. |
167 | linearSolve m b = A.mbLinearSolve m b | 194 | linearSolve m b = A.mbLinearSolve m b |
168 | 195 | ||
196 | -- | return an orthonormal basis of the null space of a matrix. See also 'nullspaceSVD'. | ||
197 | nullspace m = nullspaceSVD (Left (1*eps)) m (rightSV m) | ||
198 | |||
199 | -- | return an orthonormal basis of the range space of a matrix. See also 'orthSVD'. | ||
200 | orth m = orthSVD (Left (1*eps)) m (leftSV m) | ||
201 | |||
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs index 324fb44..4824af4 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Util.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs | |||
@@ -32,7 +32,7 @@ module Numeric.LinearAlgebra.Util( | |||
32 | rand, randn, | 32 | rand, randn, |
33 | cross, | 33 | cross, |
34 | norm, | 34 | norm, |
35 | ℕ,ℤ,ℝ,ℂ,𝑖,i_C, --ℍ | 35 | ℕ,ℤ,ℝ,ℂ,iC, |
36 | Normed(..), norm_Frob, norm_nuclear, | 36 | Normed(..), norm_Frob, norm_nuclear, |
37 | unitary, | 37 | unitary, |
38 | mt, | 38 | mt, |
@@ -72,13 +72,10 @@ type ℝ = Double | |||
72 | type ℕ = Int | 72 | type ℕ = Int |
73 | type ℤ = Int | 73 | type ℤ = Int |
74 | type ℂ = Complex Double | 74 | type ℂ = Complex Double |
75 | --type ℝn = Vector ℝ | ||
76 | --type ℂn = Vector ℂ | ||
77 | --newtype ℍ m = H m | ||
78 | 75 | ||
79 | i_C, 𝑖 :: ℂ | 76 | -- | imaginary unit |
80 | 𝑖 = 0:+1 | 77 | iC :: ℂ |
81 | i_C = 𝑖 | 78 | iC = 0:+1 |
82 | 79 | ||
83 | {- | create a real vector | 80 | {- | create a real vector |
84 | 81 | ||
diff --git a/packages/base/src/Numeric/Sparse.hs b/packages/base/src/Numeric/Sparse.hs index 1b8a7b3..f495e3a 100644 --- a/packages/base/src/Numeric/Sparse.hs +++ b/packages/base/src/Numeric/Sparse.hs | |||
@@ -62,7 +62,26 @@ mkCSR sm' = CSR{..} | |||
62 | csrNRows = dim csrRows - 1 | 62 | csrNRows = dim csrRows - 1 |
63 | csrNCols = fromIntegral (V.maximum csrCols) | 63 | csrNCols = fromIntegral (V.maximum csrCols) |
64 | 64 | ||
65 | 65 | {- | General matrix with specialized internal representations for | |
66 | dense, sparse, diagonal, banded, and constant elements. | ||
67 | |||
68 | >>> let m = mkSparse [((0,999),1.0),((1,1999),2.0)] | ||
69 | >>> m | ||
70 | SparseR {gmCSR = CSR {csrVals = fromList [1.0,2.0], | ||
71 | csrCols = fromList [1000,2000], | ||
72 | csrRows = fromList [1,2,3], | ||
73 | csrNRows = 2, | ||
74 | csrNCols = 2000}, | ||
75 | nRows = 2, | ||
76 | nCols = 2000} | ||
77 | |||
78 | >>> let m = mkDense (mat 2 [1..4]) | ||
79 | >>> m | ||
80 | Dense {gmDense = (2><2) | ||
81 | [ 1.0, 2.0 | ||
82 | , 3.0, 4.0 ], nRows = 2, nCols = 2} | ||
83 | |||
84 | -} | ||
66 | data GMatrix | 85 | data GMatrix |
67 | = SparseR | 86 | = SparseR |
68 | { gmCSR :: CSR | 87 | { gmCSR :: CSR |
@@ -146,7 +165,13 @@ gmXv Dense{..} v | |||
146 | nRows nCols (dim v) | 165 | nRows nCols (dim v) |
147 | 166 | ||
148 | 167 | ||
149 | -- | general matrix - vector product | 168 | {- | general matrix - vector product |
169 | |||
170 | >>> let m = mkSparse [((0,999),1.0),((1,1999),2.0)] | ||
171 | >>> m !#> vect[1..2000] | ||
172 | fromList [1000.0,4000.0] | ||
173 | |||
174 | -} | ||
150 | infixr 8 !#> | 175 | infixr 8 !#> |
151 | (!#>) :: GMatrix -> Vector Double -> Vector Double | 176 | (!#>) :: GMatrix -> Vector Double -> Vector Double |
152 | (!#>) = gmXv | 177 | (!#>) = gmXv |