diff options
Diffstat (limited to 'packages/base/src/Numeric')
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Data.hs | 59 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/HMatrix.hs | 5 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Static.hs | 16 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs | 3 | ||||
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Util.hs | 16 | ||||
-rw-r--r-- | packages/base/src/Numeric/Sparse.hs | 4 | ||||
-rw-r--r-- | packages/base/src/Numeric/Vector.hs | 2 |
7 files changed, 63 insertions, 42 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Data.hs b/packages/base/src/Numeric/LinearAlgebra/Data.hs index 8a0b9a2..2aac2e4 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Data.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Data.hs | |||
@@ -1,7 +1,7 @@ | |||
1 | -------------------------------------------------------------------------------- | 1 | -------------------------------------------------------------------------------- |
2 | {- | | 2 | {- | |
3 | Module : Numeric.LinearAlgebra.Data | 3 | Module : Numeric.LinearAlgebra.Data |
4 | Copyright : (c) Alberto Ruiz 2014 | 4 | Copyright : (c) Alberto Ruiz 2015 |
5 | License : BSD3 | 5 | License : BSD3 |
6 | Maintainer : Alberto Ruiz | 6 | Maintainer : Alberto Ruiz |
7 | Stability : provisional | 7 | Stability : provisional |
@@ -15,62 +15,76 @@ module Numeric.LinearAlgebra.Data( | |||
15 | 15 | ||
16 | -- * Vector | 16 | -- * Vector |
17 | -- | 1D arrays are storable vectors from the vector package. | 17 | -- | 1D arrays are storable vectors from the vector package. |
18 | 18 | ||
19 | vector, (|>), | 19 | vector, (|>), |
20 | 20 | ||
21 | -- * Matrix | 21 | -- * Matrix |
22 | 22 | ||
23 | matrix, (><), tr, | 23 | matrix, (><), tr, tr', |
24 | 24 | ||
25 | -- * Dimensions | ||
26 | |||
27 | size, rows, cols, | ||
28 | |||
29 | -- * conversion from\/to lists | ||
30 | fromList, toList, | ||
31 | fromLists, toLists, | ||
32 | row, col, | ||
33 | |||
34 | -- * conversions vector\/matrix | ||
35 | |||
36 | flatten, reshape, asRow, asColumn, | ||
37 | fromRows, toRows, fromColumns, toColumns, | ||
38 | |||
25 | -- * Indexing | 39 | -- * Indexing |
26 | 40 | ||
27 | size, | 41 | atIndex, |
28 | Indexable(..), | 42 | Indexable(..), |
29 | 43 | ||
30 | -- * Construction | 44 | -- * Construction |
31 | scalar, Konst(..), Build(..), assoc, accum, linspace, range, idxs, -- ones, zeros, | 45 | scalar, Konst(..), Build(..), assoc, accum, linspace, range, idxs, -- ones, zeros, |
32 | 46 | ||
33 | -- * Diagonal | 47 | -- * Diagonal |
34 | ident, diag, diagl, diagRect, takeDiag, | 48 | ident, diag, diagl, diagRect, takeDiag, |
35 | 49 | ||
36 | -- * Data manipulation | 50 | -- * Vector extraction |
37 | fromList, toList, subVector, takesV, vjoin, | 51 | subVector, takesV, vjoin, |
38 | flatten, reshape, asRow, asColumn, row, col, | 52 | |
39 | fromRows, toRows, fromColumns, toColumns, fromLists, toLists, fromArray2D, | 53 | -- * Matrix extraction |
40 | Extractor(..), (??), | 54 | Extractor(..), (??), |
41 | takeRows, dropRows, takeColumns, dropColumns, subMatrix, (?), (¿), fliprl, flipud, | 55 | takeRows, dropRows, takeColumns, dropColumns, subMatrix, (?), (¿), fliprl, flipud, |
42 | 56 | ||
57 | |||
43 | -- * Block matrix | 58 | -- * Block matrix |
44 | fromBlocks, (|||), (===), diagBlock, repmat, toBlocks, toBlocksEvery, | 59 | fromBlocks, (|||), (===), diagBlock, repmat, toBlocks, toBlocksEvery, |
45 | 60 | ||
46 | -- * Mapping functions | 61 | -- * Mapping functions |
47 | conj, cmap, cmod, step, cond, | 62 | conj, cmap, cmod, step, cond, |
48 | 63 | ||
49 | -- * Find elements | 64 | -- * Find elements |
50 | find, maxIndex, minIndex, maxElement, minElement, atIndex, | 65 | find, maxIndex, minIndex, maxElement, minElement, |
51 | sortVector, | 66 | sortVector, sortIndex, |
52 | 67 | ||
53 | -- * Sparse | 68 | -- * Sparse |
54 | AssocMatrix, toDense, | 69 | AssocMatrix, toDense, |
55 | mkSparse, mkDiagR, mkDense, | 70 | mkSparse, mkDiagR, mkDense, |
56 | 71 | ||
57 | -- * IO | 72 | -- * IO |
58 | disp, | 73 | disp, |
59 | loadMatrix, loadMatrix', saveMatrix, | 74 | loadMatrix, loadMatrix', saveMatrix, |
60 | latexFormat, | 75 | latexFormat, |
61 | dispf, disps, dispcf, format, | 76 | dispf, disps, dispcf, format, |
62 | dispDots, dispBlanks, dispShort, | 77 | dispDots, dispBlanks, dispShort, |
63 | -- * Conversion | 78 | -- * Element conversion |
64 | Convert(..), | 79 | Convert(..), |
65 | roundVector, | 80 | roundVector, |
66 | fromInt, | 81 | fromInt, |
67 | -- * Misc | 82 | -- * Misc |
68 | arctan2, | 83 | arctan2, |
69 | rows, cols, | ||
70 | separable, | 84 | separable, |
71 | (¦),(——), | 85 | fromArray2D, |
72 | module Data.Complex, | 86 | module Data.Complex, |
73 | CInt, Idxs, | 87 | I, |
74 | Vector, Matrix, GMatrix, nRows, nCols | 88 | Vector, Matrix, GMatrix, nRows, nCols |
75 | 89 | ||
76 | ) where | 90 | ) where |
@@ -81,7 +95,6 @@ import Data.Packed.Numeric | |||
81 | import Numeric.LinearAlgebra.Util hiding ((&),(#)) | 95 | import Numeric.LinearAlgebra.Util hiding ((&),(#)) |
82 | import Data.Complex | 96 | import Data.Complex |
83 | import Numeric.Sparse | 97 | import Numeric.Sparse |
84 | import Data.Packed.Internal.Vector(Idxs) | 98 | import Data.Packed.Internal.Numeric(I,Extractor(..),(??),fromInt,range,idxs) |
85 | import Data.Packed.Internal.Numeric(CInt,Extractor(..),(??),fromInt,range,idxs) | ||
86 | 99 | ||
87 | 100 | ||
diff --git a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs index 8e67eb4..54f066b 100644 --- a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs +++ b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs | |||
@@ -10,8 +10,11 @@ Stability : provisional | |||
10 | -------------------------------------------------------------------------------- | 10 | -------------------------------------------------------------------------------- |
11 | 11 | ||
12 | module Numeric.LinearAlgebra.HMatrix ( | 12 | module Numeric.LinearAlgebra.HMatrix ( |
13 | module Numeric.LinearAlgebra | 13 | module Numeric.LinearAlgebra, |
14 | (¦),(——) | ||
14 | ) where | 15 | ) where |
15 | 16 | ||
16 | import Numeric.LinearAlgebra | 17 | import Numeric.LinearAlgebra |
18 | import Numeric.LinearAlgebra.Util | ||
17 | 19 | ||
20 | |||
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs index f7017e7..49327f2 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs | |||
@@ -34,7 +34,7 @@ module Numeric.LinearAlgebra.Static( | |||
34 | linspace, range, dim, | 34 | linspace, range, dim, |
35 | -- * Matrix | 35 | -- * Matrix |
36 | L, Sq, build, | 36 | L, Sq, build, |
37 | row, col, (¦),(——), splitRows, splitCols, | 37 | row, col, (|||),(===), splitRows, splitCols, |
38 | unrow, uncol, | 38 | unrow, uncol, |
39 | tr, | 39 | tr, |
40 | eye, | 40 | eye, |
@@ -61,7 +61,7 @@ module Numeric.LinearAlgebra.Static( | |||
61 | 61 | ||
62 | import GHC.TypeLits | 62 | 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,eigSH', |
67 | eigenvalues,eigenvaluesSH,eigenvaluesSH',build, | 67 | eigenvalues,eigenvaluesSH,eigenvaluesSH',build, |
@@ -168,14 +168,14 @@ unrow = mkR . head . LA.toRows . ud2 | |||
168 | uncol v = unrow . tr $ v | 168 | uncol v = unrow . tr $ v |
169 | 169 | ||
170 | 170 | ||
171 | infixl 2 —— | 171 | infixl 2 === |
172 | (——) :: (KnownNat r1, KnownNat r2, KnownNat c) => L r1 c -> L r2 c -> L (r1+r2) c | 172 | (===) :: (KnownNat r1, KnownNat r2, KnownNat c) => L r1 c -> L r2 c -> L (r1+r2) c |
173 | a —— b = mkL (extract a LA.—— extract b) | 173 | a === b = mkL (extract a LA.=== extract b) |
174 | 174 | ||
175 | 175 | ||
176 | infixl 3 ¦ | 176 | infixl 3 ||| |
177 | -- (¦) :: (KnownNat r, KnownNat c1, KnownNat c2) => L r c1 -> L r c2 -> L r (c1+c2) | 177 | -- (|||) :: (KnownNat r, KnownNat c1, KnownNat c2) => L r c1 -> L r c2 -> L r (c1+c2) |
178 | a ¦ b = tr (tr a —— tr b) | 178 | a ||| b = tr (tr a === tr b) |
179 | 179 | ||
180 | 180 | ||
181 | type Sq n = L n n | 181 | type Sq n = L n n |
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs index 7ecb132..7b770e0 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs | |||
@@ -244,11 +244,14 @@ instance (KnownNat n, KnownNat m) => Transposable (L m n) (L n m) | |||
244 | where | 244 | where |
245 | tr a@(isDiag -> Just _) = mkL (extract a) | 245 | tr a@(isDiag -> Just _) = mkL (extract a) |
246 | tr (extract -> a) = mkL (tr a) | 246 | tr (extract -> a) = mkL (tr a) |
247 | tr' = tr | ||
247 | 248 | ||
248 | instance (KnownNat n, KnownNat m) => Transposable (M m n) (M n m) | 249 | instance (KnownNat n, KnownNat m) => Transposable (M m n) (M n m) |
249 | where | 250 | where |
250 | tr a@(isDiagC -> Just _) = mkM (extract a) | 251 | tr a@(isDiagC -> Just _) = mkM (extract a) |
251 | tr (extract -> a) = mkM (tr a) | 252 | tr (extract -> a) = mkM (tr a) |
253 | tr' a@(isDiagC -> Just _) = mkM (extract a) | ||
254 | tr' (extract -> a) = mkM (tr' a) | ||
252 | 255 | ||
253 | -------------------------------------------------------------------------------- | 256 | -------------------------------------------------------------------------------- |
254 | 257 | ||
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs index 2e632b7..eadd2a2 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Util.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs | |||
@@ -66,7 +66,7 @@ import Control.Monad(when) | |||
66 | import Text.Printf | 66 | import Text.Printf |
67 | import Data.List.Split(splitOn) | 67 | import Data.List.Split(splitOn) |
68 | import Data.List(intercalate) | 68 | import Data.List(intercalate) |
69 | import Foreign.C.Types(CInt) | 69 | import Data.Packed.Internal.Numeric(I) |
70 | 70 | ||
71 | type ℝ = Double | 71 | type ℝ = Double |
72 | type ℕ = Int | 72 | type ℕ = Int |
@@ -271,7 +271,7 @@ instance Normed (Matrix ℂ) | |||
271 | norm_2 = pnorm PNorm2 | 271 | norm_2 = pnorm PNorm2 |
272 | norm_Inf = pnorm Infinity | 272 | norm_Inf = pnorm Infinity |
273 | 273 | ||
274 | instance Normed (Vector CInt) | 274 | instance Normed (Vector I) |
275 | where | 275 | where |
276 | norm_0 = fromIntegral . sumElements . step . abs | 276 | norm_0 = fromIntegral . sumElements . step . abs |
277 | norm_1 = fromIntegral . norm1 | 277 | norm_1 = fromIntegral . norm1 |
@@ -299,7 +299,7 @@ mt = trans . inv | |||
299 | -------------------------------------------------------------------------------- | 299 | -------------------------------------------------------------------------------- |
300 | {- | | 300 | {- | |
301 | 301 | ||
302 | >>> size $ fromList[1..10::Double] | 302 | >>> size $ vector [1..10] |
303 | 10 | 303 | 10 |
304 | >>> size $ (2><5)[1..10::Double] | 304 | >>> size $ (2><5)[1..10::Double] |
305 | (2,5) | 305 | (2,5) |
@@ -308,15 +308,15 @@ mt = trans . inv | |||
308 | size :: Container c t => c t -> IndexOf c | 308 | size :: Container c t => c t -> IndexOf c |
309 | size = size' | 309 | size = size' |
310 | 310 | ||
311 | {- | | 311 | {- | Alternative indexing function. |
312 | 312 | ||
313 | >>> vect [1..10] ! 3 | 313 | >>> vector [1..10] ! 3 |
314 | 4.0 | 314 | 4.0 |
315 | 315 | ||
316 | >>> mat 5 [1..15] ! 1 | 316 | >>> matrix 5 [1..15] ! 1 |
317 | fromList [6.0,7.0,8.0,9.0,10.0] | 317 | fromList [6.0,7.0,8.0,9.0,10.0] |
318 | 318 | ||
319 | >>> mat 5 [1..15] ! 1 ! 3 | 319 | >>> matrix 5 [1..15] ! 1 ! 3 |
320 | 9.0 | 320 | 9.0 |
321 | 321 | ||
322 | -} | 322 | -} |
@@ -333,7 +333,7 @@ instance Indexable (Vector Float) Float | |||
333 | where | 333 | where |
334 | (!) = (@>) | 334 | (!) = (@>) |
335 | 335 | ||
336 | instance Indexable (Vector CInt) CInt | 336 | instance Indexable (Vector I) I |
337 | where | 337 | where |
338 | (!) = (@>) | 338 | (!) = (@>) |
339 | 339 | ||
diff --git a/packages/base/src/Numeric/Sparse.hs b/packages/base/src/Numeric/Sparse.hs index f1516ec..d856287 100644 --- a/packages/base/src/Numeric/Sparse.hs +++ b/packages/base/src/Numeric/Sparse.hs | |||
@@ -195,10 +195,12 @@ toDense asm = assoc (r+1,c+1) 0 asm | |||
195 | instance Transposable CSR CSC | 195 | instance Transposable CSR CSC |
196 | where | 196 | where |
197 | tr (CSR vs cs rs n m) = CSC vs cs rs m n | 197 | tr (CSR vs cs rs n m) = CSC vs cs rs m n |
198 | tr' = tr | ||
198 | 199 | ||
199 | instance Transposable CSC CSR | 200 | instance Transposable CSC CSR |
200 | where | 201 | where |
201 | tr (CSC vs rs cs n m) = CSR vs rs cs m n | 202 | tr (CSC vs rs cs n m) = CSR vs rs cs m n |
203 | tr' = tr | ||
202 | 204 | ||
203 | instance Transposable GMatrix GMatrix | 205 | instance Transposable GMatrix GMatrix |
204 | where | 206 | where |
@@ -206,5 +208,5 @@ instance Transposable GMatrix GMatrix | |||
206 | tr (SparseC s n m) = SparseR (tr s) m n | 208 | tr (SparseC s n m) = SparseR (tr s) m n |
207 | tr (Diag v n m) = Diag v m n | 209 | tr (Diag v n m) = Diag v m n |
208 | tr (Dense a n m) = Dense (tr a) m n | 210 | tr (Dense a n m) = Dense (tr a) m n |
209 | 211 | tr' = tr | |
210 | 212 | ||
diff --git a/packages/base/src/Numeric/Vector.hs b/packages/base/src/Numeric/Vector.hs index 6cac5dc..6245cf7 100644 --- a/packages/base/src/Numeric/Vector.hs +++ b/packages/base/src/Numeric/Vector.hs | |||
@@ -32,7 +32,7 @@ adaptScalar f1 f2 f3 x y | |||
32 | 32 | ||
33 | ------------------------------------------------------------------ | 33 | ------------------------------------------------------------------ |
34 | 34 | ||
35 | instance Num (Vector CInt) where | 35 | instance Num (Vector I) where |
36 | (+) = adaptScalar addConstant add (flip addConstant) | 36 | (+) = adaptScalar addConstant add (flip addConstant) |
37 | negate = scale (-1) | 37 | negate = scale (-1) |
38 | (*) = adaptScalar scale mul (flip scale) | 38 | (*) = adaptScalar scale mul (flip scale) |