summaryrefslogtreecommitdiff
path: root/packages
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2015-05-26 20:14:56 +0200
committerAlberto Ruiz <aruiz@um.es>2015-05-26 20:14:56 +0200
commit9a640d084f3d950e37e054672c9bbbefe4af06d7 (patch)
treec9016bbf1f28848aeef61aae4c0d6715d188f296 /packages
parentf38aba5c0086e662a9e49043f414d03a0dacb044 (diff)
tr' , documentation
Diffstat (limited to 'packages')
-rw-r--r--packages/base/src/Data/Packed/Foreign.hs1
-rw-r--r--packages/base/src/Data/Packed/Internal/Vector.hs5
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Data.hs59
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/HMatrix.hs5
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static.hs16
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs3
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Util.hs16
-rw-r--r--packages/base/src/Numeric/Sparse.hs4
-rw-r--r--packages/base/src/Numeric/Vector.hs2
9 files changed, 65 insertions, 46 deletions
diff --git a/packages/base/src/Data/Packed/Foreign.hs b/packages/base/src/Data/Packed/Foreign.hs
index 1ec3694..85b8bc7 100644
--- a/packages/base/src/Data/Packed/Foreign.hs
+++ b/packages/base/src/Data/Packed/Foreign.hs
@@ -16,7 +16,6 @@ module Data.Packed.Foreign
16import Data.Packed.Internal 16import Data.Packed.Internal
17import qualified Data.Vector.Storable as S 17import qualified Data.Vector.Storable as S
18import Foreign (Ptr, ForeignPtr, Storable) 18import Foreign (Ptr, ForeignPtr, Storable)
19import Foreign.C.Types (CInt)
20import GHC.Base (IO(..), realWorld#) 19import GHC.Base (IO(..), realWorld#)
21 20
22{-# INLINE unsafeInlinePerformIO #-} 21{-# INLINE unsafeInlinePerformIO #-}
diff --git a/packages/base/src/Data/Packed/Internal/Vector.hs b/packages/base/src/Data/Packed/Internal/Vector.hs
index ac35596..ac019a8 100644
--- a/packages/base/src/Data/Packed/Internal/Vector.hs
+++ b/packages/base/src/Data/Packed/Internal/Vector.hs
@@ -25,7 +25,7 @@ module Data.Packed.Internal.Vector (
25 unsafeToForeignPtr, 25 unsafeToForeignPtr,
26 unsafeFromForeignPtr, 26 unsafeFromForeignPtr,
27 unsafeWith, 27 unsafeWith,
28 CInt,Idxs 28 CInt, I
29) where 29) where
30 30
31import Data.Packed.Internal.Common 31import Data.Packed.Internal.Common
@@ -56,8 +56,7 @@ import Data.Vector.Storable(Vector,
56 unsafeFromForeignPtr, 56 unsafeFromForeignPtr,
57 unsafeWith) 57 unsafeWith)
58 58
59 59type I = CInt
60type Idxs = Vector CInt
61 60
62-- | Number of elements 61-- | Number of elements
63dim :: (Storable t) => Vector t -> Int 62dim :: (Storable t) => Vector t -> Int
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{- |
3Module : Numeric.LinearAlgebra.Data 3Module : Numeric.LinearAlgebra.Data
4Copyright : (c) Alberto Ruiz 2014 4Copyright : (c) Alberto Ruiz 2015
5License : BSD3 5License : BSD3
6Maintainer : Alberto Ruiz 6Maintainer : Alberto Ruiz
7Stability : provisional 7Stability : 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
81import Numeric.LinearAlgebra.Util hiding ((&),(#)) 95import Numeric.LinearAlgebra.Util hiding ((&),(#))
82import Data.Complex 96import Data.Complex
83import Numeric.Sparse 97import Numeric.Sparse
84import Data.Packed.Internal.Vector(Idxs) 98import Data.Packed.Internal.Numeric(I,Extractor(..),(??),fromInt,range,idxs)
85import 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
12module Numeric.LinearAlgebra.HMatrix ( 12module Numeric.LinearAlgebra.HMatrix (
13 module Numeric.LinearAlgebra 13 module Numeric.LinearAlgebra,
14 (¦),(——)
14) where 15) where
15 16
16import Numeric.LinearAlgebra 17import Numeric.LinearAlgebra
18import 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
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,
@@ -168,14 +168,14 @@ unrow = mkR . head . LA.toRows . ud2
168uncol v = unrow . tr $ v 168uncol v = unrow . tr $ v
169 169
170 170
171infixl 2 —— 171infixl 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
173a —— b = mkL (extract a LA.—— extract b) 173a === b = mkL (extract a LA.=== extract b)
174 174
175 175
176infixl 3 ¦ 176infixl 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)
178a ¦ b = tr (tr a —— tr b) 178a ||| b = tr (tr a === tr b)
179 179
180 180
181type Sq n = L n n 181type 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
248instance (KnownNat n, KnownNat m) => Transposable (M m n) (M n m) 249instance (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)
66import Text.Printf 66import Text.Printf
67import Data.List.Split(splitOn) 67import Data.List.Split(splitOn)
68import Data.List(intercalate) 68import Data.List(intercalate)
69import Foreign.C.Types(CInt) 69import Data.Packed.Internal.Numeric(I)
70 70
71type ℝ = Double 71type ℝ = Double
72type ℕ = Int 72type ℕ = 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
274instance Normed (Vector CInt) 274instance 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]
30310 30310
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
308size :: Container c t => c t -> IndexOf c 308size :: Container c t => c t -> IndexOf c
309size = size' 309size = size'
310 310
311{- | 311{- | Alternative indexing function.
312 312
313>>> vect [1..10] ! 3 313>>> vector [1..10] ! 3
3144.0 3144.0
315 315
316>>> mat 5 [1..15] ! 1 316>>> matrix 5 [1..15] ! 1
317fromList [6.0,7.0,8.0,9.0,10.0] 317fromList [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
3209.0 3209.0
321 321
322-} 322-}
@@ -333,7 +333,7 @@ instance Indexable (Vector Float) Float
333 where 333 where
334 (!) = (@>) 334 (!) = (@>)
335 335
336instance Indexable (Vector CInt) CInt 336instance 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
195instance Transposable CSR CSC 195instance 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
199instance Transposable CSC CSR 200instance 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
203instance Transposable GMatrix GMatrix 205instance 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
35instance Num (Vector CInt) where 35instance 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)