summaryrefslogtreecommitdiff
path: root/lib/Numeric/Container.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Numeric/Container.hs')
-rw-r--r--lib/Numeric/Container.hs557
1 files changed, 60 insertions, 497 deletions
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
index 6b73a4e..b3f46de 100644
--- a/lib/Numeric/Container.hs
+++ b/lib/Numeric/Container.hs
@@ -26,13 +26,24 @@
26----------------------------------------------------------------------------- 26-----------------------------------------------------------------------------
27 27
28module Numeric.Container ( 28module Numeric.Container (
29 -- * Basic functions
30 module Data.Packed,
31 constant, linspace,
32 diag, ident,
33 ctrans,
29 -- * Generic operations 34 -- * Generic operations
30 Container(..), 35 Container(..),
31 -- * Matrix product and related functions 36 -- * Matrix product
32 Product(..), 37 Product(..),
33 mXm,mXv,vXm, 38 optimiseMult,
39 mXm,mXv,vXm,(<.>),(<>),(<\>),
34 outer, kronecker, 40 outer, kronecker,
35 41 -- * Random numbers
42 RandDist(..),
43 randomVector,
44 gaussianSample,
45 uniformSample,
46 meanCov,
36 -- * Element conversion 47 -- * Element conversion
37 Convert(..), 48 Convert(..),
38 Complexable(), 49 Complexable(),
@@ -42,6 +53,11 @@ module Numeric.Container (
42 53
43 IndexOf, 54 IndexOf,
44 module Data.Complex, 55 module Data.Complex,
56 -- * Input / Output
57 dispf, disps, dispcf, vecdisp, latexFormat, format,
58 loadMatrix, saveMatrix, fromFile, fileDimensions,
59 readMatrix,
60 fscanfVector, fprintfVector, freadVector, fwriteVector,
45 -- * Experimental 61 -- * Experimental
46 build', konst', 62 build', konst',
47 -- * Deprecated 63 -- * Deprecated
@@ -51,517 +67,64 @@ module Numeric.Container (
51) where 67) where
52 68
53import Data.Packed 69import Data.Packed
54import Numeric.Conversion 70import Data.Packed.Internal(constantD)
55import Data.Packed.Internal 71import Numeric.ContainerBoot
56import Numeric.GSL.Vector 72import Numeric.Chain
57 73import Numeric.IO
58import Data.Complex 74import Data.Complex
59import Control.Monad(ap) 75import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD)
60 76import Data.Packed.Random
61import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ)
62
63import System.IO.Unsafe
64
65-------------------------------------------------------------------
66
67type family IndexOf c
68
69type instance IndexOf Vector = Int
70type instance IndexOf Matrix = (Int,Int)
71
72type family ArgOf c a
73
74type instance ArgOf Vector a = a -> a
75type instance ArgOf Matrix a = a -> a -> a
76
77-------------------------------------------------------------------
78
79-- | Basic element-by-element functions for numeric containers
80class (Complexable c, Fractional e, Element e) => Container c e where
81 -- | create a structure with a single element
82 scalar :: e -> c e
83 -- | complex conjugate
84 conj :: c e -> c e
85 scale :: e -> c e -> c e
86 -- | scale the element by element reciprocal of the object:
87 --
88 -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@
89 scaleRecip :: e -> c e -> c e
90 addConstant :: e -> c e -> c e
91 add :: c e -> c e -> c e
92 sub :: c e -> c e -> c e
93 -- | element by element multiplication
94 mul :: c e -> c e -> c e
95 -- | element by element division
96 divide :: c e -> c e -> c e
97 equal :: c e -> c e -> Bool
98 --
99 -- | cannot implement instance Functor because of Element class constraint
100 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b
101 -- | constant structure of given size
102 konst :: e -> IndexOf c -> c e
103 -- | create a structure using a function
104 --
105 -- Hilbert matrix of order N:
106 --
107 -- @hilb n = build (n,n) (\\i j -> 1/(i+j+1))@
108 build :: IndexOf c -> (ArgOf c e) -> c e
109 --build :: BoundsOf f -> f -> (ContainerOf f) e
110 --
111 -- | indexing function
112 atIndex :: c e -> IndexOf c -> e
113 -- | index of min element
114 minIndex :: c e -> IndexOf c
115 -- | index of max element
116 maxIndex :: c e -> IndexOf c
117 -- | value of min element
118 minElement :: c e -> e
119 -- | value of max element
120 maxElement :: c e -> e
121 -- the C functions sumX/prodX are twice as fast as using foldVector
122 -- | the sum of elements (faster than using @fold@)
123 sumElements :: c e -> e
124 -- | the product of elements (faster than using @fold@)
125 prodElements :: c e -> e
126
127--------------------------------------------------------------------------
128
129instance Container Vector Float where
130 scale = vectorMapValF Scale
131 scaleRecip = vectorMapValF Recip
132 addConstant = vectorMapValF AddConstant
133 add = vectorZipF Add
134 sub = vectorZipF Sub
135 mul = vectorZipF Mul
136 divide = vectorZipF Div
137 equal u v = dim u == dim v && maxElement (vectorMapF Abs (sub u v)) == 0.0
138 scalar x = fromList [x]
139 konst = constantD
140 build = buildV
141 conj = id
142 cmap = mapVector
143 atIndex = (@>)
144 minIndex = round . toScalarF MinIdx
145 maxIndex = round . toScalarF MaxIdx
146 minElement = toScalarF Min
147 maxElement = toScalarF Max
148 sumElements = sumF
149 prodElements = prodF
150
151instance Container Vector Double where
152 scale = vectorMapValR Scale
153 scaleRecip = vectorMapValR Recip
154 addConstant = vectorMapValR AddConstant
155 add = vectorZipR Add
156 sub = vectorZipR Sub
157 mul = vectorZipR Mul
158 divide = vectorZipR Div
159 equal u v = dim u == dim v && maxElement (vectorMapR Abs (sub u v)) == 0.0
160 scalar x = fromList [x]
161 konst = constantD
162 build = buildV
163 conj = id
164 cmap = mapVector
165 atIndex = (@>)
166 minIndex = round . toScalarR MinIdx
167 maxIndex = round . toScalarR MaxIdx
168 minElement = toScalarR Min
169 maxElement = toScalarR Max
170 sumElements = sumR
171 prodElements = prodR
172
173instance Container Vector (Complex Double) where
174 scale = vectorMapValC Scale
175 scaleRecip = vectorMapValC Recip
176 addConstant = vectorMapValC AddConstant
177 add = vectorZipC Add
178 sub = vectorZipC Sub
179 mul = vectorZipC Mul
180 divide = vectorZipC Div
181 equal u v = dim u == dim v && maxElement (mapVector magnitude (sub u v)) == 0.0
182 scalar x = fromList [x]
183 konst = constantD
184 build = buildV
185 conj = conjugateC
186 cmap = mapVector
187 atIndex = (@>)
188 minIndex = minIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
189 maxIndex = maxIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
190 minElement = ap (@>) minIndex
191 maxElement = ap (@>) maxIndex
192 sumElements = sumC
193 prodElements = prodC
194
195instance Container Vector (Complex Float) where
196 scale = vectorMapValQ Scale
197 scaleRecip = vectorMapValQ Recip
198 addConstant = vectorMapValQ AddConstant
199 add = vectorZipQ Add
200 sub = vectorZipQ Sub
201 mul = vectorZipQ Mul
202 divide = vectorZipQ Div
203 equal u v = dim u == dim v && maxElement (mapVector magnitude (sub u v)) == 0.0
204 scalar x = fromList [x]
205 konst = constantD
206 build = buildV
207 conj = conjugateQ
208 cmap = mapVector
209 atIndex = (@>)
210 minIndex = minIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
211 maxIndex = maxIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate)
212 minElement = ap (@>) minIndex
213 maxElement = ap (@>) maxIndex
214 sumElements = sumQ
215 prodElements = prodQ
216
217---------------------------------------------------------------
218
219instance (Container Vector a) => Container Matrix a where
220 scale x = liftMatrix (scale x)
221 scaleRecip x = liftMatrix (scaleRecip x)
222 addConstant x = liftMatrix (addConstant x)
223 add = liftMatrix2 add
224 sub = liftMatrix2 sub
225 mul = liftMatrix2 mul
226 divide = liftMatrix2 divide
227 equal a b = cols a == cols b && flatten a `equal` flatten b
228 scalar x = (1><1) [x]
229 konst v (r,c) = reshape c (konst v (r*c))
230 build = buildM
231 conj = liftMatrix conj
232 cmap f = liftMatrix (mapVector f)
233 atIndex = (@@>)
234 minIndex m = let (r,c) = (rows m,cols m)
235 i = (minIndex $ flatten m)
236 in (i `div` c,i `mod` c)
237 maxIndex m = let (r,c) = (rows m,cols m)
238 i = (maxIndex $ flatten m)
239 in (i `div` c,i `mod` c)
240 minElement = ap (@@>) minIndex
241 maxElement = ap (@@>) maxIndex
242 sumElements = sumElements . flatten
243 prodElements = prodElements . flatten
244
245----------------------------------------------------
246
247-- | Matrix product and related functions
248class Element e => Product e where
249 -- | matrix product
250 multiply :: Matrix e -> Matrix e -> Matrix e
251 -- | dot (inner) product
252 dot :: Vector e -> Vector e -> e
253 -- | sum of absolute value of elements (differs in complex case from @norm1@)
254 absSum :: Vector e -> RealOf e
255 -- | sum of absolute value of elements
256 norm1 :: Vector e -> RealOf e
257 -- | euclidean norm
258 norm2 :: Vector e -> RealOf e
259 -- | element of maximum magnitude
260 normInf :: Vector e -> RealOf e
261
262instance Product Float where
263 norm2 = toScalarF Norm2
264 absSum = toScalarF AbsSum
265 dot = dotF
266 norm1 = toScalarF AbsSum
267 normInf = maxElement . vectorMapF Abs
268 multiply = multiplyF
269 77
270instance Product Double where 78------------------------------------------------------------------
271 norm2 = toScalarR Norm2
272 absSum = toScalarR AbsSum
273 dot = dotR
274 norm1 = toScalarR AbsSum
275 normInf = maxElement . vectorMapR Abs
276 multiply = multiplyR
277 79
278instance Product (Complex Float) where 80{- | creates a vector with a given number of equal components:
279 norm2 = toScalarQ Norm2
280 absSum = toScalarQ AbsSum
281 dot = dotQ
282 norm1 = sumElements . fst . fromComplex . vectorMapQ Abs
283 normInf = maxElement . fst . fromComplex . vectorMapQ Abs
284 multiply = multiplyQ
285 81
286instance Product (Complex Double) where 82@> constant 2 7
287 norm2 = toScalarC Norm2 837 |> [2.0,2.0,2.0,2.0,2.0,2.0,2.0]@
288 absSum = toScalarC AbsSum
289 dot = dotC
290 norm1 = sumElements . fst . fromComplex . vectorMapC Abs
291 normInf = maxElement . fst . fromComplex . vectorMapC Abs
292 multiply = multiplyC
293
294----------------------------------------------------------
295
296-- synonym for matrix product
297mXm :: Product t => Matrix t -> Matrix t -> Matrix t
298mXm = multiply
299
300-- matrix - vector product
301mXv :: Product t => Matrix t -> Vector t -> Vector t
302mXv m v = flatten $ m `mXm` (asColumn v)
303
304-- vector - matrix product
305vXm :: Product t => Vector t -> Matrix t -> Vector t
306vXm v m = flatten $ (asRow v) `mXm` m
307
308{- | Outer product of two vectors.
309
310@\> 'fromList' [1,2,3] \`outer\` 'fromList' [5,2,3]
311(3><3)
312 [ 5.0, 2.0, 3.0
313 , 10.0, 4.0, 6.0
314 , 15.0, 6.0, 9.0 ]@
315-} 84-}
316outer :: (Product t) => Vector t -> Vector t -> Matrix t 85constant :: Element a => a -> Int -> Vector a
317outer u v = asColumn u `multiply` asRow v 86-- constant x n = runSTVector (newVector x n)
318 87constant = constantD-- about 2x faster
319{- | Kronecker product of two matrices.
320
321@m1=(2><3)
322 [ 1.0, 2.0, 0.0
323 , 0.0, -1.0, 3.0 ]
324m2=(4><3)
325 [ 1.0, 2.0, 3.0
326 , 4.0, 5.0, 6.0
327 , 7.0, 8.0, 9.0
328 , 10.0, 11.0, 12.0 ]@
329
330@\> kronecker m1 m2
331(8><9)
332 [ 1.0, 2.0, 3.0, 2.0, 4.0, 6.0, 0.0, 0.0, 0.0
333 , 4.0, 5.0, 6.0, 8.0, 10.0, 12.0, 0.0, 0.0, 0.0
334 , 7.0, 8.0, 9.0, 14.0, 16.0, 18.0, 0.0, 0.0, 0.0
335 , 10.0, 11.0, 12.0, 20.0, 22.0, 24.0, 0.0, 0.0, 0.0
336 , 0.0, 0.0, 0.0, -1.0, -2.0, -3.0, 3.0, 6.0, 9.0
337 , 0.0, 0.0, 0.0, -4.0, -5.0, -6.0, 12.0, 15.0, 18.0
338 , 0.0, 0.0, 0.0, -7.0, -8.0, -9.0, 21.0, 24.0, 27.0
339 , 0.0, 0.0, 0.0, -10.0, -11.0, -12.0, 30.0, 33.0, 36.0 ]@
340-}
341kronecker :: (Product t) => Matrix t -> Matrix t -> Matrix t
342kronecker a b = fromBlocks
343 . splitEvery (cols a)
344 . map (reshape (cols b))
345 . toRows
346 $ flatten a `outer` flatten b
347
348-------------------------------------------------------------------
349
350
351class Convert t where
352 real :: Container c t => c (RealOf t) -> c t
353 complex :: Container c t => c t -> c (ComplexOf t)
354 single :: Container c t => c t -> c (SingleOf t)
355 double :: Container c t => c t -> c (DoubleOf t)
356 toComplex :: (Container c t, RealElement t) => (c t, c t) -> c (Complex t)
357 fromComplex :: (Container c t, RealElement t) => c (Complex t) -> (c t, c t)
358
359
360instance Convert Double where
361 real = id
362 complex = comp'
363 single = single'
364 double = id
365 toComplex = toComplex'
366 fromComplex = fromComplex'
367
368instance Convert Float where
369 real = id
370 complex = comp'
371 single = id
372 double = double'
373 toComplex = toComplex'
374 fromComplex = fromComplex'
375
376instance Convert (Complex Double) where
377 real = comp'
378 complex = id
379 single = single'
380 double = id
381 toComplex = toComplex'
382 fromComplex = fromComplex'
383
384instance Convert (Complex Float) where
385 real = comp'
386 complex = id
387 single = id
388 double = double'
389 toComplex = toComplex'
390 fromComplex = fromComplex'
391
392-------------------------------------------------------------------
393
394type family RealOf x
395
396type instance RealOf Double = Double
397type instance RealOf (Complex Double) = Double
398 88
399type instance RealOf Float = Float 89{- | Creates a real vector containing a range of values:
400type instance RealOf (Complex Float) = Float
401 90
402type family ComplexOf x 91@\> linspace 5 (-3,7)
925 |> [-3.0,-0.5,2.0,4.5,7.0]@
403 93
404type instance ComplexOf Double = Complex Double 94Logarithmic spacing can be defined as follows:
405type instance ComplexOf (Complex Double) = Complex Double
406 95
407type instance ComplexOf Float = Complex Float 96@logspace n (a,b) = 10 ** linspace n (a,b)@
408type instance ComplexOf (Complex Float) = Complex Float
409
410type family SingleOf x
411
412type instance SingleOf Double = Float
413type instance SingleOf Float = Float
414
415type instance SingleOf (Complex a) = Complex (SingleOf a)
416
417type family DoubleOf x
418
419type instance DoubleOf Double = Double
420type instance DoubleOf Float = Double
421
422type instance DoubleOf (Complex a) = Complex (DoubleOf a)
423
424type family ElementOf c
425
426type instance ElementOf (Vector a) = a
427type instance ElementOf (Matrix a) = a
428
429------------------------------------------------------------
430
431conjugateAux fun x = unsafePerformIO $ do
432 v <- createVector (dim x)
433 app2 fun vec x vec v "conjugateAux"
434 return v
435
436conjugateQ :: Vector (Complex Float) -> Vector (Complex Float)
437conjugateQ = conjugateAux c_conjugateQ
438foreign import ccall "conjugateQ" c_conjugateQ :: TQVQV
439
440conjugateC :: Vector (Complex Double) -> Vector (Complex Double)
441conjugateC = conjugateAux c_conjugateC
442foreign import ccall "conjugateC" c_conjugateC :: TCVCV
443
444----------------------------------------------------
445
446{-# DEPRECATED (.*) "use scale a x or scalar a * x" #-}
447
448-- -- | @x .* a = scale x a@
449-- (.*) :: (Linear c a) => a -> c a -> c a
450infixl 7 .*
451a .* x = scale a x
452
453----------------------------------------------------
454
455{-# DEPRECATED (*/) "use scale (recip a) x or x / scalar a" #-}
456
457-- -- | @a *\/ x = scale (recip x) a@
458-- (*/) :: (Linear c a) => c a -> a -> c a
459infixl 7 */
460v */ x = scale (recip x) v
461
462
463------------------------------------------------
464
465{-# DEPRECATED (<|>) "define operator a & b = fromBlocks[[a,b]] and use asRow/asColumn to join vectors" #-}
466{-# DEPRECATED (<->) "define operator a // b = fromBlocks[[a],[b]] and use asRow/asColumn to join vectors" #-}
467
468class Joinable a b where
469 joinH :: Element t => a t -> b t -> Matrix t
470 joinV :: Element t => a t -> b t -> Matrix t
471
472instance Joinable Matrix Matrix where
473 joinH m1 m2 = fromBlocks [[m1,m2]]
474 joinV m1 m2 = fromBlocks [[m1],[m2]]
475
476instance Joinable Matrix Vector where
477 joinH m v = joinH m (asColumn v)
478 joinV m v = joinV m (asRow v)
479
480instance Joinable Vector Matrix where
481 joinH v m = joinH (asColumn v) m
482 joinV v m = joinV (asRow v) m
483
484infixl 4 <|>
485infixl 3 <->
486
487{-- - | Horizontal concatenation of matrices and vectors:
488
489@> (ident 3 \<-\> 3 * ident 3) \<|\> fromList [1..6.0]
490(6><4)
491 [ 1.0, 0.0, 0.0, 1.0
492 , 0.0, 1.0, 0.0, 2.0
493 , 0.0, 0.0, 1.0, 3.0
494 , 3.0, 0.0, 0.0, 4.0
495 , 0.0, 3.0, 0.0, 5.0
496 , 0.0, 0.0, 3.0, 6.0 ]@
497-} 97-}
498-- (<|>) :: (Element t, Joinable a b) => a t -> b t -> Matrix t 98linspace :: (Enum e, Container Vector e) => Int -> (e, e) -> Vector e
499a <|> b = joinH a b 99linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1]
500 100 where s = (b-a)/fromIntegral (n-1)
501-- -- | Vertical concatenation of matrices and vectors.
502-- (<->) :: (Element t, Joinable a b) => a t -> b t -> Matrix t
503a <-> b = joinV a b
504
505-------------------------------------------------------------------
506
507{-# DEPRECATED vectorMin "use minElement" #-}
508vectorMin :: (Container Vector t, Element t) => Vector t -> t
509vectorMin = minElement
510
511{-# DEPRECATED vectorMax "use maxElement" #-}
512vectorMax :: (Container Vector t, Element t) => Vector t -> t
513vectorMax = maxElement
514
515
516{-# DEPRECATED vectorMaxIndex "use minIndex" #-}
517vectorMaxIndex :: Vector Double -> Int
518vectorMaxIndex = round . toScalarR MaxIdx
519
520{-# DEPRECATED vectorMinIndex "use maxIndex" #-}
521vectorMinIndex :: Vector Double -> Int
522vectorMinIndex = round . toScalarR MinIdx
523
524-----------------------------------------------------
525
526class Build f where
527 build' :: BoundsOf f -> f -> ContainerOf f
528
529type family BoundsOf x
530
531type instance BoundsOf (a->a) = Int
532type instance BoundsOf (a->a->a) = (Int,Int)
533
534type family ContainerOf x
535
536type instance ContainerOf (a->a) = Vector a
537type instance ContainerOf (a->a->a) = Matrix a
538 101
539instance (Element a, Num a) => Build (a->a) where 102-- | Dot product: @u \<.\> v = dot u v@
540 build' = buildV 103(<.>) :: Product t => Vector t -> Vector t -> t
104infixl 7 <.>
105(<.>) = dot
541 106
542instance (Element a, Num a) => Build (a->a->a) where
543 build' = buildM
544 107
545buildM (rc,cc) f = fromLists [ [f r c | c <- cs] | r <- rs ]
546 where rs = map fromIntegral [0 .. (rc-1)]
547 cs = map fromIntegral [0 .. (cc-1)]
548 108
549buildV n f = fromList [f k | k <- ks] 109--------------------------------------------------------
550 where ks = map fromIntegral [0 .. (n-1)]
551 110
552---------------------------------------------------- 111class Mul a b c | a b -> c where
553-- experimental 112 infixl 7 <>
113 -- | Matrix-matrix, matrix-vector, and vector-matrix products.
114 (<>) :: Product t => a t -> b t -> c t
554 115
555class Konst s where 116instance Mul Matrix Matrix Matrix where
556 konst' :: Element e => e -> s -> ContainerOf' s e 117 (<>) = mXm
557 118
558type family ContainerOf' x y 119instance Mul Matrix Vector Vector where
120 (<>) m v = flatten $ m <> (asColumn v)
559 121
560type instance ContainerOf' Int a = Vector a 122instance Mul Vector Matrix Vector where
561type instance ContainerOf' (Int,Int) a = Matrix a 123 (<>) v m = flatten $ (asRow v) <> m
562 124
563instance Konst Int where 125--------------------------------------------------------
564 konst' = constantD
565 126
566instance Konst (Int,Int) where 127-- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD).
567 konst' k (r,c) = reshape c $ konst' k (r*c) 128(<\>) :: (Field a) => Matrix a -> Vector a -> Vector a
129infixl 7 <\>
130m <\> v = flatten (linearSolveSVD m (reshape 1 v))