summaryrefslogtreecommitdiff
path: root/lib/Numeric
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Numeric')
-rw-r--r--lib/Numeric/Container.hs10
-rw-r--r--lib/Numeric/ContainerBoot.hs62
-rw-r--r--lib/Numeric/HMatrix.hs2
-rw-r--r--lib/Numeric/HMatrix/Data.hs2
-rw-r--r--lib/Numeric/HMatrix/Devel.hs4
-rw-r--r--lib/Numeric/IO.hs6
-rw-r--r--lib/Numeric/LinearAlgebra/Util.hs18
7 files changed, 64 insertions, 40 deletions
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
index b145a26..dea8a79 100644
--- a/lib/Numeric/Container.hs
+++ b/lib/Numeric/Container.hs
@@ -86,15 +86,19 @@ constant = constantD-- about 2x faster
86 86
87{- | Creates a real vector containing a range of values: 87{- | Creates a real vector containing a range of values:
88 88
89>>> linspace 5 (-3,7) 89>>> linspace 5 (-3,7::Double)
90fromList [-3.0,-0.5,2.0,4.5,7.0]@ 90fromList [-3.0,-0.5,2.0,4.5,7.0]@
91 91
92>>> linspace 5 (8,2+i) :: Vector (Complex Double)
93fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]
94
92Logarithmic spacing can be defined as follows: 95Logarithmic spacing can be defined as follows:
93 96
94@logspace n (a,b) = 10 ** linspace n (a,b)@ 97@logspace n (a,b) = 10 ** linspace n (a,b)@
95-} 98-}
96linspace :: (Enum e, Container Vector e) => Int -> (e, e) -> Vector e 99linspace :: (Container Vector e) => Int -> (e, e) -> Vector e
97linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1] 100linspace 0 (a,b) = fromList[(a+b)/2]
101linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1]
98 where s = (b-a)/fromIntegral (n-1) 102 where s = (b-a)/fromIntegral (n-1)
99 103
100-- | dot product: @cdot u v = 'udot' ('conj' u) v@ 104-- | dot product: @cdot u v = 'udot' ('conj' u) v@
diff --git a/lib/Numeric/ContainerBoot.hs b/lib/Numeric/ContainerBoot.hs
index 6445e04..ea4262c 100644
--- a/lib/Numeric/ContainerBoot.hs
+++ b/lib/Numeric/ContainerBoot.hs
@@ -45,7 +45,7 @@ import Numeric.Conversion
45import Data.Packed.Internal 45import Data.Packed.Internal
46import Numeric.GSL.Vector 46import Numeric.GSL.Vector
47import Data.Complex 47import Data.Complex
48import Control.Monad(ap) 48import Control.Applicative((<*>))
49 49
50import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ) 50import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ)
51 51
@@ -206,10 +206,10 @@ instance Container Vector Float where
206 conj = id 206 conj = id
207 cmap = mapVector 207 cmap = mapVector
208 atIndex = (@>) 208 atIndex = (@>)
209 minIndex = round . toScalarF MinIdx 209 minIndex = emptyErrorV "minIndex" (round . toScalarF MinIdx)
210 maxIndex = round . toScalarF MaxIdx 210 maxIndex = emptyErrorV "maxIndex" (round . toScalarF MaxIdx)
211 minElement = toScalarF Min 211 minElement = emptyErrorV "minElement" (toScalarF Min)
212 maxElement = toScalarF Max 212 maxElement = emptyErrorV "maxElement" (toScalarF Max)
213 sumElements = sumF 213 sumElements = sumF
214 prodElements = prodF 214 prodElements = prodF
215 step = stepF 215 step = stepF
@@ -234,10 +234,10 @@ instance Container Vector Double where
234 conj = id 234 conj = id
235 cmap = mapVector 235 cmap = mapVector
236 atIndex = (@>) 236 atIndex = (@>)
237 minIndex = round . toScalarR MinIdx 237 minIndex = emptyErrorV "minIndex" (round . toScalarR MinIdx)
238 maxIndex = round . toScalarR MaxIdx 238 maxIndex = emptyErrorV "maxIndex" (round . toScalarR MaxIdx)
239 minElement = toScalarR Min 239 minElement = emptyErrorV "minElement" (toScalarR Min)
240 maxElement = toScalarR Max 240 maxElement = emptyErrorV "maxElement" (toScalarR Max)
241 sumElements = sumR 241 sumElements = sumR
242 prodElements = prodR 242 prodElements = prodR
243 step = stepD 243 step = stepD
@@ -262,10 +262,10 @@ instance Container Vector (Complex Double) where
262 conj = conjugateC 262 conj = conjugateC
263 cmap = mapVector 263 cmap = mapVector
264 atIndex = (@>) 264 atIndex = (@>)
265 minIndex = minIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) 265 minIndex = emptyErrorV "minIndex" (minIndex . fst . fromComplex . (mul <*> conj))
266 maxIndex = maxIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) 266 maxIndex = emptyErrorV "maxIndex" (maxIndex . fst . fromComplex . (mul <*> conj))
267 minElement = ap (@>) minIndex 267 minElement = emptyErrorV "minElement" (atIndex <*> minIndex)
268 maxElement = ap (@>) maxIndex 268 maxElement = emptyErrorV "maxElement" (atIndex <*> maxIndex)
269 sumElements = sumC 269 sumElements = sumC
270 prodElements = prodC 270 prodElements = prodC
271 step = undefined -- cannot match 271 step = undefined -- cannot match
@@ -290,10 +290,10 @@ instance Container Vector (Complex Float) where
290 conj = conjugateQ 290 conj = conjugateQ
291 cmap = mapVector 291 cmap = mapVector
292 atIndex = (@>) 292 atIndex = (@>)
293 minIndex = minIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) 293 minIndex = emptyErrorV "minIndex" (minIndex . fst . fromComplex . (mul <*> conj))
294 maxIndex = maxIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) 294 maxIndex = emptyErrorV "maxIndex" (maxIndex . fst . fromComplex . (mul <*> conj))
295 minElement = ap (@>) minIndex 295 minElement = emptyErrorV "minElement" (atIndex <*> minIndex)
296 maxElement = ap (@>) maxIndex 296 maxElement = emptyErrorV "maxElement" (atIndex <*> maxIndex)
297 sumElements = sumQ 297 sumElements = sumQ
298 prodElements = prodQ 298 prodElements = prodQ
299 step = undefined -- cannot match 299 step = undefined -- cannot match
@@ -320,14 +320,12 @@ instance (Container Vector a) => Container Matrix a where
320 conj = liftMatrix conj 320 conj = liftMatrix conj
321 cmap f = liftMatrix (mapVector f) 321 cmap f = liftMatrix (mapVector f)
322 atIndex = (@@>) 322 atIndex = (@@>)
323 minIndex m = let (r,c) = (rows m,cols m) 323 minIndex = emptyErrorM "minIndex of Matrix" $
324 i = (minIndex $ flatten m) 324 \m -> divMod (minIndex $ flatten m) (cols m)
325 in (i `div` c,i `mod` c) 325 maxIndex = emptyErrorM "maxIndex of Matrix" $
326 maxIndex m = let (r,c) = (rows m,cols m) 326 \m -> divMod (maxIndex $ flatten m) (cols m)
327 i = (maxIndex $ flatten m) 327 minElement = emptyErrorM "minElement of Matrix" (atIndex <*> minIndex)
328 in (i `div` c,i `mod` c) 328 maxElement = emptyErrorM "maxElement of Matrix" (atIndex <*> maxIndex)
329 minElement = ap (@@>) minIndex
330 maxElement = ap (@@>) maxIndex
331 sumElements = sumElements . flatten 329 sumElements = sumElements . flatten
332 prodElements = prodElements . flatten 330 prodElements = prodElements . flatten
333 step = liftMatrix step 331 step = liftMatrix step
@@ -336,6 +334,17 @@ instance (Container Vector a) => Container Matrix a where
336 accum = accumM 334 accum = accumM
337 cond = condM 335 cond = condM
338 336
337
338emptyErrorV msg f v =
339 if dim v > 0
340 then f v
341 else error $ msg ++ " of Vector with dim = 0"
342
343emptyErrorM msg f m =
344 if rows m > 0 && cols m > 0
345 then f m
346 else error $ msg++" "++shSize m
347
339---------------------------------------------------- 348----------------------------------------------------
340 349
341-- | Matrix product and related functions 350-- | Matrix product and related functions
@@ -393,7 +402,6 @@ emptyVal f v =
393 then f v 402 then f v
394 else 0 403 else 0
395 404
396
397-- FIXME remove unused C wrappers 405-- FIXME remove unused C wrappers
398-- | (unconjugated) dot product 406-- | (unconjugated) dot product
399udot :: Product e => Vector e -> Vector e -> e 407udot :: Product e => Vector e -> Vector e -> e
@@ -592,7 +600,7 @@ accumM m0 f xs = ST.runSTMatrix $ do
592 600
593---------------------------------------------------------------------- 601----------------------------------------------------------------------
594 602
595condM a b l e t = reshape (cols a'') $ cond a' b' l' e' t' 603condM a b l e t = matrixFromVector RowMajor (rows a'') (cols a'') $ cond a' b' l' e' t'
596 where 604 where
597 args@(a'':_) = conformMs [a,b,l,e,t] 605 args@(a'':_) = conformMs [a,b,l,e,t]
598 [a', b', l', e', t'] = map flatten args 606 [a', b', l', e', t'] = map flatten args
diff --git a/lib/Numeric/HMatrix.hs b/lib/Numeric/HMatrix.hs
index a2f09df..f49ea53 100644
--- a/lib/Numeric/HMatrix.hs
+++ b/lib/Numeric/HMatrix.hs
@@ -114,7 +114,7 @@ module Numeric.HMatrix (
114 orth, 114 orth,
115 115
116 -- * Norms 116 -- * Norms
117 norm1, norm2, normInf, 117 norm1, norm2, normInf, pnorm, NormType(..),
118 118
119 -- * Correlation and Convolution 119 -- * Correlation and Convolution
120 corr, conv, corrMin, corr2, conv2, 120 corr, conv, corrMin, corr2, conv2,
diff --git a/lib/Numeric/HMatrix/Data.hs b/lib/Numeric/HMatrix/Data.hs
index 288b0af..568dc05 100644
--- a/lib/Numeric/HMatrix/Data.hs
+++ b/lib/Numeric/HMatrix/Data.hs
@@ -44,7 +44,7 @@ module Numeric.HMatrix.Data(
44 find, maxIndex, minIndex, maxElement, minElement, atIndex, 44 find, maxIndex, minIndex, maxElement, minElement, atIndex,
45 45
46 -- * IO 46 -- * IO
47 disp, dispf, disps, dispcf, vecdisp, latexFormat, format, 47 disp, dispf, disps, dispcf, latexFormat, format,
48 loadMatrix, saveMatrix, fromFile, fileDimensions, 48 loadMatrix, saveMatrix, fromFile, fileDimensions,
49 readMatrix, 49 readMatrix,
50 fscanfVector, fprintfVector, freadVector, fwriteVector, 50 fscanfVector, fprintfVector, freadVector, fwriteVector,
diff --git a/lib/Numeric/HMatrix/Devel.hs b/lib/Numeric/HMatrix/Devel.hs
index 7363477..b921f44 100644
--- a/lib/Numeric/HMatrix/Devel.hs
+++ b/lib/Numeric/HMatrix/Devel.hs
@@ -55,7 +55,7 @@ module Numeric.HMatrix.Devel(
55 Complexable(), RealElement(), 55 Complexable(), RealElement(),
56 RealOf, ComplexOf, SingleOf, DoubleOf, 56 RealOf, ComplexOf, SingleOf, DoubleOf,
57 IndexOf, 57 IndexOf,
58 Field, 58 Field, Normed
59) where 59) where
60 60
61import Data.Packed.Foreign 61import Data.Packed.Foreign
@@ -65,5 +65,5 @@ import Numeric.Container(Container,Contraction,LSDiv,Product,
65 Complexable(),RealElement(), 65 Complexable(),RealElement(),
66 RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf) 66 RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf)
67import Data.Packed 67import Data.Packed
68import Numeric.LinearAlgebra.Algorithms(Field) 68import Numeric.LinearAlgebra.Algorithms(Field,Normed)
69 69
diff --git a/lib/Numeric/IO.hs b/lib/Numeric/IO.hs
index 57275ac..836f352 100644
--- a/lib/Numeric/IO.hs
+++ b/lib/Numeric/IO.hs
@@ -60,6 +60,9 @@ disps d x = sdims x ++ " " ++ formatScaled d x
603.00 3.50 4.00 4.50 603.00 3.50 4.00 4.50
615.00 5.50 6.00 6.50 615.00 5.50 6.00 6.50
62 62
63>>> putStr . unlines . tail . lines . dispf 2 . asRow $ linspace 10 (0,1)
640.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00
65
63-} 66-}
64dispf :: Int -> Matrix Double -> String 67dispf :: Int -> Matrix Double -> String
65dispf d x = sdims x ++ "\n" ++ formatFixed (if isInt x then 0 else d) x 68dispf d x = sdims x ++ "\n" ++ formatFixed (if isInt x then 0 else d) x
@@ -74,7 +77,8 @@ formatScaled dec t = "E"++show o++"\n" ++ ss
74 where ss = format " " (printf fmt. g) t 77 where ss = format " " (printf fmt. g) t
75 g x | o >= 0 = x/10^(o::Int) 78 g x | o >= 0 = x/10^(o::Int)
76 | otherwise = x*10^(-o) 79 | otherwise = x*10^(-o)
77 o = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t 80 o | rows t == 0 || cols t == 0 = 0
81 | otherwise = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t
78 fmt = '%':show (dec+3) ++ '.':show dec ++"f" 82 fmt = '%':show (dec+3) ++ '.':show dec ++"f"
79 83
80{- | Show a vector using a function for showing matrices. 84{- | Show a vector using a function for showing matrices.
diff --git a/lib/Numeric/LinearAlgebra/Util.hs b/lib/Numeric/LinearAlgebra/Util.hs
index 7164827..7d134bf 100644
--- a/lib/Numeric/LinearAlgebra/Util.hs
+++ b/lib/Numeric/LinearAlgebra/Util.hs
@@ -166,7 +166,7 @@ row = asRow . fromList
166col :: [Double] -> Matrix Double 166col :: [Double] -> Matrix Double
167col = asColumn . fromList 167col = asColumn . fromList
168 168
169{- | extract selected rows 169{- | extract rows
170 170
171>>> (20><4) [1..] ? [2,1,1] 171>>> (20><4) [1..] ? [2,1,1]
172(3><4) 172(3><4)
@@ -179,12 +179,20 @@ infixl 9 ?
179(?) :: Element t => Matrix t -> [Int] -> Matrix t 179(?) :: Element t => Matrix t -> [Int] -> Matrix t
180(?) = flip extractRows 180(?) = flip extractRows
181 181
182-- | extract selected columns 182{- | extract columns
183-- 183
184-- (unicode 0x00bf, inverted question mark) 184(unicode 0x00bf, inverted question mark, Alt-Gr ?)
185
186>>> (3><4) [1..] ¿ [3,0]
187(3><2)
188 [ 4.0, 1.0
189 , 8.0, 5.0
190 , 12.0, 9.0 ]
191
192-}
185infixl 9 ¿ 193infixl 9 ¿
186(¿) :: Element t => Matrix t -> [Int] -> Matrix t 194(¿) :: Element t => Matrix t -> [Int] -> Matrix t
187m ¿ ks = trans . extractRows ks . trans $ m 195(¿)= flip extractColumns
188 196
189 197
190cross :: Vector Double -> Vector Double -> Vector Double 198cross :: Vector Double -> Vector Double -> Vector Double