summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/LinearAlgebra
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra')
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Data.hs19
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/HMatrix.hs5
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static.hs16
3 files changed, 26 insertions, 14 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Data.hs b/packages/base/src/Numeric/LinearAlgebra/Data.hs
index fffc2bd..2a45771 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Data.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Data.hs
@@ -1,3 +1,5 @@
1{-# LANGUAGE TypeOperators #-}
2
1-------------------------------------------------------------------------------- 3--------------------------------------------------------------------------------
2{- | 4{- |
3Module : Numeric.LinearAlgebra.Data 5Module : Numeric.LinearAlgebra.Data
@@ -17,11 +19,11 @@ module Numeric.LinearAlgebra.Data(
17 -- | 1D arrays are storable vectors from the vector package. There is no distinction 19 -- | 1D arrays are storable vectors from the vector package. There is no distinction
18 -- between row and column vectors. 20 -- between row and column vectors.
19 21
20 fromList, toList, vector, (|>), 22 fromList, toList, (|>), vector, range, idxs,
21 23
22 -- * Matrix 24 -- * Matrix
23 25
24 matrix, (><), tr, tr', 26 (><), matrix, tr, tr',
25 27
26 -- * Dimensions 28 -- * Dimensions
27 29
@@ -43,7 +45,7 @@ module Numeric.LinearAlgebra.Data(
43 Indexable(..), 45 Indexable(..),
44 46
45 -- * Construction 47 -- * Construction
46 scalar, Konst(..), Build(..), assoc, accum, linspace, range, idxs, -- ones, zeros, 48 scalar, Konst(..), Build(..), assoc, accum, linspace, -- ones, zeros,
47 49
48 -- * Diagonal 50 -- * Diagonal
49 ident, diag, diagl, diagRect, takeDiag, 51 ident, diag, diagl, diagRect, takeDiag,
@@ -53,16 +55,19 @@ module Numeric.LinearAlgebra.Data(
53 55
54 -- * Matrix extraction 56 -- * Matrix extraction
55 Extractor(..), (??), 57 Extractor(..), (??),
58
56 takeRows, dropRows, takeColumns, dropColumns, 59 takeRows, dropRows, takeColumns, dropColumns,
57 subMatrix, (?), (¿), fliprl, flipud, remap, 60 subMatrix, (?), (¿), fliprl, flipud,
61
62 remap,
58 63
59 -- * Block matrix 64 -- * Block matrix
60 fromBlocks, (|||), (===), diagBlock, repmat, toBlocks, toBlocksEvery, 65 fromBlocks, (|||), (===), diagBlock, repmat, toBlocks, toBlocksEvery,
61 66
62 -- * Mapping functions 67 -- * Mapping functions
63 conj, cmap, cmod, 68 conj, cmap, cmod,
64 69
65 step, cond, ccompare, cselect, 70 step, cond,
66 71
67 -- * Find elements 72 -- * Find elements
68 find, maxIndex, minIndex, maxElement, minElement, 73 find, maxIndex, minIndex, maxElement, minElement,
@@ -87,7 +92,7 @@ module Numeric.LinearAlgebra.Data(
87 separable, 92 separable,
88 fromArray2D, 93 fromArray2D,
89 module Data.Complex, 94 module Data.Complex,
90 R,C,I,Z,Mod, 95 R,C,I,Z,Mod, type(./.),
91 Vector, Matrix, GMatrix, nRows, nCols 96 Vector, Matrix, GMatrix, nRows, nCols
92 97
93) where 98) where
diff --git a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs
index 11c2487..8adaaaf 100644
--- a/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/HMatrix.hs
@@ -13,10 +13,13 @@ compatibility with previous version, to be removed
13 13
14module Numeric.LinearAlgebra.HMatrix ( 14module Numeric.LinearAlgebra.HMatrix (
15 module Numeric.LinearAlgebra, 15 module Numeric.LinearAlgebra,
16 (¦),(——),ℝ,ℂ, 16 (¦),(——),ℝ,ℂ,(<·>)
17) where 17) where
18 18
19import Numeric.LinearAlgebra 19import Numeric.LinearAlgebra
20import Internal.Util 20import Internal.Util
21 21
22infixr 8 <·>
23(<·>) :: Numeric t => Vector t -> Vector t -> t
24(<·>) = dot
22 25
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs
index a657bd0..d0a790d 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Static.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs
@@ -44,7 +44,7 @@ module Numeric.LinearAlgebra.Static(
44 -- * Complex 44 -- * Complex
45 C, M, Her, her, 𝑖, 45 C, M, Her, her, 𝑖,
46 -- * Products 46 -- * Products
47 (<>),(#>),(<·>), 47 (<>),(#>),(<.>),
48 -- * Linear Systems 48 -- * Linear Systems
49 linSolve, (<\>), 49 linSolve, (<\>),
50 -- * Factorizations 50 -- * Factorizations
@@ -55,13 +55,13 @@ module Numeric.LinearAlgebra.Static(
55 Disp(..), Domain(..), 55 Disp(..), Domain(..),
56 withVector, withMatrix, 56 withVector, withMatrix,
57 toRows, toColumns, 57 toRows, toColumns,
58 Sized(..), Diag(..), Sym, sym, mTm, unSym 58 Sized(..), Diag(..), Sym, sym, mTm, unSym, (<·>)
59) where 59) where
60 60
61 61
62import GHC.TypeLits 62import GHC.TypeLits
63import Numeric.LinearAlgebra hiding ( 63import 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,
@@ -207,6 +207,10 @@ infixr 8 <·>
207(<·>) :: R n -> R n -> ℝ 207(<·>) :: R n -> R n -> ℝ
208(<·>) = dotR 208(<·>) = dotR
209 209
210infixr 8 <.>
211(<.>) :: R n -> R n -> ℝ
212(<.>) = dotR
213
210-------------------------------------------------------------------------------- 214--------------------------------------------------------------------------------
211 215
212class Diag m d | m -> d 216class Diag m d | m -> d
@@ -496,7 +500,7 @@ appC m v = mkC (extract m LA.#> extract v)
496dotC :: KnownNat n => C n -> C n -> ℂ 500dotC :: KnownNat n => C n -> C n -> ℂ
497dotC (unwrap -> u) (unwrap -> v) 501dotC (unwrap -> u) (unwrap -> v)
498 | singleV u || singleV v = sumElements (conj u * v) 502 | singleV u || singleV v = sumElements (conj u * v)
499 | otherwise = u LA.<·> v 503 | otherwise = u LA.<.> v
500 504
501 505
502crossC :: C 3 -> C 3 -> C 3 506crossC :: C 3 -> C 3 -> C 3
@@ -584,12 +588,12 @@ test = (ok,info)
584 where 588 where
585 q = tm :: L 10 3 589 q = tm :: L 10 3
586 590
587 thingD = vjoin [ud1 u, 1] LA.<·> tr m LA.#> m LA.#> ud1 v 591 thingD = vjoin [ud1 u, 1] LA.<.> tr m LA.#> m LA.#> ud1 v
588 where 592 where
589 m = LA.matrix 3 [1..30] 593 m = LA.matrix 3 [1..30]
590 594
591 precS = (1::Double) + (2::Double) * ((1 :: R 3) * (u & 6)) <·> konst 2 #> v 595 precS = (1::Double) + (2::Double) * ((1 :: R 3) * (u & 6)) <·> konst 2 #> v
592 precD = 1 + 2 * vjoin[ud1 u, 6] LA.<·> LA.konst 2 (LA.size (ud1 u) +1, LA.size (ud1 v)) LA.#> ud1 v 596 precD = 1 + 2 * vjoin[ud1 u, 6] LA.<.> LA.konst 2 (LA.size (ud1 u) +1, LA.size (ud1 v)) LA.#> ud1 v
593 597
594 598
595splittest 599splittest