summaryrefslogtreecommitdiff
path: root/packages/base
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2015-06-05 16:44:52 +0200
committerAlberto Ruiz <aruiz@um.es>2015-06-05 16:44:52 +0200
commit64df799c68817054705a99e9ee02723603fae29e (patch)
treebf1f5b04eb9984c230d295905570330c026337e1 /packages/base
parent11d7c37dc8b314338bc6382d80e74aaec2bb5620 (diff)
move internal numeric
Diffstat (limited to 'packages/base')
-rw-r--r--packages/base/src/Internal/Numeric.hs (renamed from packages/base/src/Data/Packed/Internal/Numeric.hs)77
1 files changed, 14 insertions, 63 deletions
diff --git a/packages/base/src/Data/Packed/Internal/Numeric.hs b/packages/base/src/Internal/Numeric.hs
index a03159d..86a4a4c 100644
--- a/packages/base/src/Data/Packed/Internal/Numeric.hs
+++ b/packages/base/src/Internal/Numeric.hs
@@ -16,41 +16,17 @@
16-- 16--
17----------------------------------------------------------------------------- 17-----------------------------------------------------------------------------
18 18
19module Data.Packed.Internal.Numeric ( 19module Internal.Numeric where
20 -- * Basic functions 20
21 ident, diag, ctrans, 21import Internal.Tools
22 -- * Generic operations 22import Internal.Vector
23 Container(..), 23import Internal.Matrix
24 scalar, conj, scale, arctan2, cmap, cmod, 24import Internal.Element
25 atIndex, minIndex, maxIndex, minElement, maxElement, 25import Internal.ST as ST
26 sumElements, prodElements, 26import Internal.Conversion
27 step, cond, find, assoc, accum, findV, assocV, accumV, 27import Internal.Vectorized
28 Transposable(..), Linear(..), Testable(..), 28import Internal.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI)
29 -- * Matrix product and related functions 29import Data.Vector.Storable(fromList)
30 Product(..), udot,
31 mXm,mXv,vXm,
32 outer, kronecker,
33 -- * sorting
34 sortV, sortI,
35 -- * Element conversion
36 Convert(..),
37 Complexable(),
38 RealElement(),
39 roundVector, fromInt, toInt,
40 RealOf, ComplexOf, SingleOf, DoubleOf,
41 IndexOf,
42 I, Extractor(..), (??), range, idxs, remapM,
43 module Data.Complex
44) where
45
46import Data.Packed
47import Data.Packed.ST as ST
48import Numeric.Conversion
49import Data.Packed.Development
50import Numeric.Vectorized
51import Data.Complex
52import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI)
53import Data.Packed.Internal
54import Text.Printf(printf) 30import Text.Printf(printf)
55 31
56------------------------------------------------------------------- 32-------------------------------------------------------------------
@@ -78,9 +54,6 @@ data Extractor
78 | DropLast Int 54 | DropLast Int
79 deriving Show 55 deriving Show
80 56
81-- | Create a vector of indexes, useful for matrix extraction using '??'
82idxs :: [Int] -> Vector I
83idxs js = fromList (map fromIntegral js) :: Vector I
84 57
85-- 58--
86infixl 9 ?? 59infixl 9 ??
@@ -167,13 +140,6 @@ class Element e => Container c e
167 sumElements' :: c e -> e 140 sumElements' :: c e -> e
168 prodElements' :: c e -> e 141 prodElements' :: c e -> e
169 step' :: Ord e => c e -> c e 142 step' :: Ord e => c e -> c e
170 cond' :: Ord e
171 => c e -- ^ a
172 -> c e -- ^ b
173 -> c e -- ^ l
174 -> c e -- ^ e
175 -> c e -- ^ g
176 -> c e -- ^ result
177 ccompare' :: Ord e => c e -> c e -> c I 143 ccompare' :: Ord e => c e -> c e -> c I
178 cselect' :: c I -> c e -> c e -> c e -> c e 144 cselect' :: c I -> c e -> c e -> c e -> c e
179 find' :: (e -> Bool) -> c e -> [IndexOf c] 145 find' :: (e -> Bool) -> c e -> [IndexOf c]
@@ -227,7 +193,6 @@ instance Container Vector I
227 find' = findV 193 find' = findV
228 assoc' = assocV 194 assoc' = assocV
229 accum' = accumV 195 accum' = accumV
230 cond' = condV condI
231 ccompare' = compareCV compareV 196 ccompare' = compareCV compareV
232 cselect' = selectCV selectV 197 cselect' = selectCV selectV
233 scaleRecip = undefined -- cannot match 198 scaleRecip = undefined -- cannot match
@@ -264,7 +229,6 @@ instance Container Vector Float
264 find' = findV 229 find' = findV
265 assoc' = assocV 230 assoc' = assocV
266 accum' = accumV 231 accum' = accumV
267 cond' = condV condF
268 ccompare' = compareCV compareV 232 ccompare' = compareCV compareV
269 cselect' = selectCV selectV 233 cselect' = selectCV selectV
270 scaleRecip = vectorMapValF Recip 234 scaleRecip = vectorMapValF Recip
@@ -301,7 +265,6 @@ instance Container Vector Double
301 find' = findV 265 find' = findV
302 assoc' = assocV 266 assoc' = assocV
303 accum' = accumV 267 accum' = accumV
304 cond' = condV condD
305 ccompare' = compareCV compareV 268 ccompare' = compareCV compareV
306 cselect' = selectCV selectV 269 cselect' = selectCV selectV
307 scaleRecip = vectorMapValR Recip 270 scaleRecip = vectorMapValR Recip
@@ -337,8 +300,7 @@ instance Container Vector (Complex Double)
337 find' = findV 300 find' = findV
338 assoc' = assocV 301 assoc' = assocV
339 accum' = accumV 302 accum' = accumV
340 cond' = undefined -- cannot match 303 ccompare' = undefined -- cannot match
341 ccompare' = undefined
342 cselect' = selectCV selectV 304 cselect' = selectCV selectV
343 scaleRecip = vectorMapValC Recip 305 scaleRecip = vectorMapValC Recip
344 divide = vectorZipC Div 306 divide = vectorZipC Div
@@ -372,8 +334,7 @@ instance Container Vector (Complex Float)
372 find' = findV 334 find' = findV
373 assoc' = assocV 335 assoc' = assocV
374 accum' = accumV 336 accum' = accumV
375 cond' = undefined -- cannot match 337 ccompare' = undefined -- cannot match
376 ccompare' = undefined
377 cselect' = selectCV selectV 338 cselect' = selectCV selectV
378 scaleRecip = vectorMapValQ Recip 339 scaleRecip = vectorMapValQ Recip
379 divide = vectorZipQ Div 340 divide = vectorZipQ Div
@@ -411,7 +372,6 @@ instance (Num a, Element a, Container Vector a) => Container Matrix a
411 find' = findM 372 find' = findM
412 assoc' = assocM 373 assoc' = assocM
413 accum' = accumM 374 accum' = accumM
414 cond' = condM
415 ccompare' = compareM 375 ccompare' = compareM
416 cselect' = selectM 376 cselect' = selectM
417 scaleRecip x = liftMatrix (scaleRecip x) 377 scaleRecip x = liftMatrix (scaleRecip x)
@@ -546,7 +506,7 @@ cond
546 -> c e -- ^ e 506 -> c e -- ^ e
547 -> c e -- ^ g 507 -> c e -- ^ g
548 -> c e -- ^ result 508 -> c e -- ^ result
549cond = cond' 509cond a b l e g = cselect' (ccompare' a b) l e g
550 510
551 511
552-- | Find index of elements which satisfy a predicate 512-- | Find index of elements which satisfy a predicate
@@ -870,15 +830,6 @@ accumM m0 f xs = ST.runSTMatrix $ do
870 830
871---------------------------------------------------------------------- 831----------------------------------------------------------------------
872 832
873condM a b l e t = matrixFromVector RowMajor (rows a'') (cols a'') $ cond' a' b' l' e' t'
874 where
875 args@(a'':_) = conformMs [a,b,l,e,t]
876 [a', b', l', e', t'] = map flatten args
877
878condV f a b l e t = f a' b' l' e' t'
879 where
880 [a', b', l', e', t'] = conformVs [a,b,l,e,t]
881
882compareM a b = matrixFromVector RowMajor (rows a'') (cols a'') $ ccompare' a' b' 833compareM a b = matrixFromVector RowMajor (rows a'') (cols a'') $ ccompare' a' b'
883 where 834 where
884 args@(a'':_) = conformMs [a,b] 835 args@(a'':_) = conformMs [a,b]