summaryrefslogtreecommitdiff
path: root/packages/base/src/Data/Packed
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2015-06-05 16:41:04 +0200
committerAlberto Ruiz <aruiz@um.es>2015-06-05 16:41:04 +0200
commitf8420df8e9f70c77a708a1eceef7340d300d4595 (patch)
tree85a5ef546c1c8688cec72b46e9c08b1d71d6f3f2 /packages/base/src/Data/Packed
parentf20a94375c03bd6154f67fec1345e530acfc881d (diff)
move numeric/container
Diffstat (limited to 'packages/base/src/Data/Packed')
-rw-r--r--packages/base/src/Data/Packed/Numeric.hs327
1 files changed, 0 insertions, 327 deletions
diff --git a/packages/base/src/Data/Packed/Numeric.hs b/packages/base/src/Data/Packed/Numeric.hs
deleted file mode 100644
index 7d77b19..0000000
--- a/packages/base/src/Data/Packed/Numeric.hs
+++ /dev/null
@@ -1,327 +0,0 @@
1{-# LANGUAGE FlexibleContexts #-}
2{-# LANGUAGE FlexibleInstances #-}
3{-# LANGUAGE MultiParamTypeClasses #-}
4{-# LANGUAGE FunctionalDependencies #-}
5{-# LANGUAGE UndecidableInstances #-}
6
7-----------------------------------------------------------------------------
8-- |
9-- Module : Data.Packed.Numeric
10-- Copyright : (c) Alberto Ruiz 2010-14
11-- License : BSD3
12-- Maintainer : Alberto Ruiz
13-- Stability : provisional
14--
15-- Basic numeric operations on 'Vector' and 'Matrix', including conversion routines.
16--
17-- The 'Container' class is used to define optimized generic functions which work
18-- on 'Vector' and 'Matrix' with real or complex elements.
19--
20-- Some of these functions are also available in the instances of the standard
21-- numeric Haskell classes provided by "Numeric.LinearAlgebra".
22--
23-----------------------------------------------------------------------------
24{-# OPTIONS_HADDOCK hide #-}
25
26module Data.Packed.Numeric (
27 -- * Basic functions
28 module Data.Packed,
29 Konst(..), Build(..),
30 linspace,
31 diag, ident,
32 ctrans,
33 -- * Generic operations
34 Container(..), Numeric, Extractor(..), (??), range, idxs, I, remap,
35 -- add, mul, sub, divide, equal, scaleRecip, addConstant,
36 scalar, conj, scale, arctan2, cmap, cmod,
37 atIndex, minIndex, maxIndex, minElement, maxElement,
38 sumElements, prodElements,
39 step, cond, find, assoc, accum, ccompare, cselect,
40 Transposable(..), Linear(..),
41 -- * Matrix product
42 Product(..), udot, dot, (<·>), (#>), (<#), app,
43 Mul(..),
44 (<.>),
45 optimiseMult,
46 mXm,mXv,vXm,LSDiv,(<\>),
47 outer, kronecker,
48 -- * Random numbers
49 RandDist(..),
50 randomVector,
51 gaussianSample,
52 uniformSample,
53 meanCov,
54 -- * sorting
55 sortVector, sortIndex,
56 -- * Element conversion
57 Convert(..),
58 Complexable(),
59 RealElement(),
60 RealOf, ComplexOf, SingleOf, DoubleOf,
61 roundVector,fromInt,toInt,
62 IndexOf,
63 module Data.Complex,
64 -- * IO
65 module Data.Packed.IO,
66 -- * Misc
67 Testable(..)
68) where
69
70import Data.Packed
71import Data.Packed.Internal(conformMs)
72import Data.Packed.Internal.Numeric
73import Data.Complex
74import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD)
75import Data.Packed.IO
76import Numeric.LinearAlgebra.Random
77
78------------------------------------------------------------------
79
80{- | Creates a real vector containing a range of values:
81
82>>> linspace 5 (-3,7::Double)
83fromList [-3.0,-0.5,2.0,4.5,7.0]@
84
85>>> linspace 5 (8,2+i) :: Vector (Complex Double)
86fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]
87
88Logarithmic spacing can be defined as follows:
89
90@logspace n (a,b) = 10 ** linspace n (a,b)@
91-}
92linspace :: (Fractional e, Container Vector e) => Int -> (e, e) -> Vector e
93linspace 0 _ = fromList[]
94linspace 1 (a,b) = fromList[(a+b)/2]
95linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1]
96 where s = (b-a)/fromIntegral (n-1)
97
98--------------------------------------------------------------------------------
99
100infixl 7 <.>
101-- | An infix synonym for 'dot'
102(<.>) :: Numeric t => Vector t -> Vector t -> t
103(<.>) = dot
104
105
106infixr 8 <·>, #>
107
108{- | infix synonym for 'dot'
109
110>>> vector [1,2,3,4] <·> vector [-2,0,1,1]
1115.0
112
113>>> let 𝑖 = 0:+1 :: ℂ
114>>> fromList [1+𝑖,1] <·> fromList [1,1+𝑖]
1152.0 :+ 0.0
116
117(the dot symbol "·" is obtained by Alt-Gr .)
118
119-}
120(<·>) :: Numeric t => Vector t -> Vector t -> t
121(<·>) = dot
122
123
124{- | infix synonym for 'app'
125
126>>> let m = (2><3) [1..]
127>>> m
128(2><3)
129 [ 1.0, 2.0, 3.0
130 , 4.0, 5.0, 6.0 ]
131
132>>> let v = vector [10,20,30]
133
134>>> m #> v
135fromList [140.0,320.0]
136
137-}
138(#>) :: Numeric t => Matrix t -> Vector t -> Vector t
139(#>) = mXv
140
141-- | dense matrix-vector product
142app :: Numeric t => Matrix t -> Vector t -> Vector t
143app = (#>)
144
145infixl 8 <#
146-- | dense vector-matrix product
147(<#) :: Numeric t => Vector t -> Matrix t -> Vector t
148(<#) = vXm
149
150--------------------------------------------------------------------------------
151
152class Mul a b c | a b -> c where
153 infixl 7 <>
154 -- | Matrix-matrix, matrix-vector, and vector-matrix products.
155 (<>) :: Product t => a t -> b t -> c t
156
157instance Mul Matrix Matrix Matrix where
158 (<>) = mXm
159
160instance Mul Matrix Vector Vector where
161 (<>) m v = flatten $ m <> asColumn v
162
163instance Mul Vector Matrix Vector where
164 (<>) v m = flatten $ asRow v <> m
165
166--------------------------------------------------------------------------------
167
168{- | Least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD)
169
170@
171a = (3><2)
172 [ 1.0, 2.0
173 , 2.0, 4.0
174 , 2.0, -1.0 ]
175@
176
177@
178v = vector [13.0,27.0,1.0]
179@
180
181>>> let x = a <\> v
182>>> x
183fromList [3.0799999999999996,5.159999999999999]
184
185>>> a #> x
186fromList [13.399999999999999,26.799999999999997,1.0]
187
188It also admits multiple right-hand sides stored as columns in a matrix.
189
190-}
191infixl 7 <\>
192(<\>) :: (LSDiv c, Field t) => Matrix t -> c t -> c t
193(<\>) = linSolve
194
195class LSDiv c
196 where
197 linSolve :: Field t => Matrix t -> c t -> c t
198
199instance LSDiv Vector
200 where
201 linSolve m v = flatten (linearSolveSVD m (reshape 1 v))
202
203instance LSDiv Matrix
204 where
205 linSolve = linearSolveSVD
206
207--------------------------------------------------------------------------------
208
209class Konst e d c | d -> c, c -> d
210 where
211 -- |
212 -- >>> konst 7 3 :: Vector Float
213 -- fromList [7.0,7.0,7.0]
214 --
215 -- >>> konst i (3::Int,4::Int)
216 -- (3><4)
217 -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
218 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
219 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]
220 --
221 konst :: e -> d -> c e
222
223instance Container Vector e => Konst e Int Vector
224 where
225 konst = konst'
226
227instance (Num e, Container Vector e) => Konst e (Int,Int) Matrix
228 where
229 konst = konst'
230
231--------------------------------------------------------------------------------
232
233class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
234 where
235 -- |
236 -- >>> build 5 (**2) :: Vector Double
237 -- fromList [0.0,1.0,4.0,9.0,16.0]
238 --
239 -- Hilbert matrix of order N:
240 --
241 -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
242 -- >>> putStr . dispf 2 $ hilb 3
243 -- 3x3
244 -- 1.00 0.50 0.33
245 -- 0.50 0.33 0.25
246 -- 0.33 0.25 0.20
247 --
248 build :: d -> f -> c e
249
250instance Container Vector e => Build Int (e -> e) Vector e
251 where
252 build = build'
253
254instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e
255 where
256 build = build'
257
258--------------------------------------------------------------------------------
259
260-- @dot u v = 'udot' ('conj' u) v@
261dot :: (Numeric t) => Vector t -> Vector t -> t
262dot u v = udot (conj u) v
263
264--------------------------------------------------------------------------------
265
266optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t
267optimiseMult = mconcat
268
269--------------------------------------------------------------------------------
270
271
272{- | Compute mean vector and covariance matrix of the rows of a matrix.
273
274>>> meanCov $ gaussianSample 666 1000 (fromList[4,5]) (diagl[2,3])
275(fromList [4.010341078059521,5.0197204699640405],
276(2><2)
277 [ 1.9862461923890056, -1.0127225830525157e-2
278 , -1.0127225830525157e-2, 3.0373954915729318 ])
279
280-}
281meanCov :: Matrix Double -> (Vector Double, Matrix Double)
282meanCov x = (med,cov) where
283 r = rows x
284 k = 1 / fromIntegral r
285 med = konst k r `vXm` x
286 meds = konst 1 r `outer` med
287 xc = x `sub` meds
288 cov = scale (recip (fromIntegral (r-1))) (trans xc `mXm` xc)
289
290--------------------------------------------------------------------------------
291
292class ( Container Vector t
293 , Container Matrix t
294 , Konst t Int Vector
295 , Konst t (Int,Int) Matrix
296 , Product t
297 ) => Numeric t
298
299instance Numeric Double
300instance Numeric (Complex Double)
301instance Numeric Float
302instance Numeric (Complex Float)
303instance Numeric I
304
305--------------------------------------------------------------------------------
306
307sortVector :: (Ord t, Element t) => Vector t -> Vector t
308sortVector = sortV
309
310sortIndex :: (Ord t, Element t) => Vector t -> Vector I
311sortIndex = sortI
312
313ccompare :: (Ord t, Container c t) => c t -> c t -> c I
314ccompare = ccompare'
315
316cselect :: (Container c t) => c I -> c t -> c t -> c t -> c t
317cselect = cselect'
318
319remap :: Element t => Matrix I -> Matrix I -> Matrix t -> Matrix t
320remap i j m
321 | minElement i >= 0 && maxElement i < fromIntegral (rows m) &&
322 minElement j >= 0 && maxElement j < fromIntegral (cols m) = remapM i' j' m
323 | otherwise = error $ "out of range index in rmap"
324 where
325 [i',j'] = conformMs [i,j]
326
327