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.hs303
1 files changed, 0 insertions, 303 deletions
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
deleted file mode 100644
index 7e46147..0000000
--- a/lib/Numeric/Container.hs
+++ /dev/null
@@ -1,303 +0,0 @@
1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE FlexibleInstances #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-}
6{-# LANGUAGE UndecidableInstances #-}
7
8-----------------------------------------------------------------------------
9-- |
10-- Module : Numeric.Container
11-- Copyright : (c) Alberto Ruiz 2010-14
12-- License : GPL
13--
14-- Maintainer : Alberto Ruiz <aruiz@um.es>
15-- Stability : provisional
16-- Portability : portable
17--
18-- Basic numeric operations on 'Vector' and 'Matrix', including conversion routines.
19--
20-- The 'Container' class is used to define optimized generic functions which work
21-- on 'Vector' and 'Matrix' with real or complex elements.
22--
23-- Some of these functions are also available in the instances of the standard
24-- numeric Haskell classes provided by "Numeric.LinearAlgebra".
25--
26-----------------------------------------------------------------------------
27{-# OPTIONS_HADDOCK hide #-}
28
29module Numeric.Container (
30 -- * Basic functions
31 module Data.Packed,
32 konst, build,
33 constant, linspace,
34 diag, ident,
35 ctrans,
36 -- * Generic operations
37 Container(..),
38 -- * Matrix product
39 Product(..), udot,
40 Mul(..),
41 Contraction(..),
42 optimiseMult,
43 mXm,mXv,vXm,LSDiv(..), cdot, (·), dot, (<.>),
44 outer, kronecker,
45 -- * Random numbers
46 RandDist(..),
47 randomVector,
48 gaussianSample,
49 uniformSample,
50 meanCov,
51 -- * Element conversion
52 Convert(..),
53 Complexable(),
54 RealElement(),
55
56 RealOf, ComplexOf, SingleOf, DoubleOf,
57
58 IndexOf,
59 module Data.Complex,
60 -- * IO
61 dispf, disps, dispcf, vecdisp, latexFormat, format,
62 loadMatrix, saveMatrix, fromFile, fileDimensions,
63 readMatrix,
64 fscanfVector, fprintfVector, freadVector, fwriteVector,
65) where
66
67import Data.Packed
68import Data.Packed.Internal(constantD)
69import Numeric.ContainerBoot
70import Numeric.Chain
71import Numeric.IO
72import Data.Complex
73import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD)
74import Data.Packed.Random
75
76------------------------------------------------------------------
77
78{- | creates a vector with a given number of equal components:
79
80@> constant 2 7
817 |> [2.0,2.0,2.0,2.0,2.0,2.0,2.0]@
82-}
83constant :: Element a => a -> Int -> Vector a
84-- constant x n = runSTVector (newVector x n)
85constant = constantD-- about 2x faster
86
87{- | Creates a real vector containing a range of values:
88
89>>> linspace 5 (-3,7::Double)
90fromList [-3.0,-0.5,2.0,4.5,7.0]@
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
95Logarithmic spacing can be defined as follows:
96
97@logspace n (a,b) = 10 ** linspace n (a,b)@
98-}
99linspace :: (Container Vector e) => Int -> (e, e) -> Vector e
100linspace 0 (a,b) = fromList[(a+b)/2]
101linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1]
102 where s = (b-a)/fromIntegral (n-1)
103
104-- | dot product: @cdot u v = 'udot' ('conj' u) v@
105cdot :: (Container Vector t, Product t) => Vector t -> Vector t -> t
106cdot u v = udot (conj u) v
107
108--------------------------------------------------------
109
110class Contraction a b c | a b -> c, c -> a b
111 where
112 infixr 7 ×
113 {- | Matrix-matrix product, matrix-vector product, and unconjugated dot product
114
115(unicode 0x00d7, multiplication sign)
116
117Examples:
118
119>>> let a = (3><4) [1..] :: Matrix Double
120>>> let v = fromList [1,0,2,-1] :: Vector Double
121>>> let u = fromList [1,2,3] :: Vector Double
122
123>>> a
124(3><4)
125 [ 1.0, 2.0, 3.0, 4.0
126 , 5.0, 6.0, 7.0, 8.0
127 , 9.0, 10.0, 11.0, 12.0 ]
128
129matrix × matrix:
130
131>>> disp 2 (a × trans a)
1323x3
133 30 70 110
134 70 174 278
135110 278 446
136
137matrix × vector:
138
139>>> a × v
140fromList [3.0,11.0,19.0]
141
142unconjugated dot product:
143
144>>> fromList [1,i] × fromList[2*i+1,3]
1451.0 :+ 5.0
146
147(×) is right associative, so we can write:
148
149>>> u × a × v
15082.0 :: Double
151
152-}
153 (×) :: a -> b -> c
154
155instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
156 (×) = mXv
157
158instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where
159 (×) = mXm
160
161instance Contraction (Vector Double) (Vector Double) Double where
162 (×) = udot
163
164instance Contraction (Vector Float) (Vector Float) Float where
165 (×) = udot
166
167instance Contraction (Vector (Complex Double)) (Vector (Complex Double)) (Complex Double) where
168 (×) = udot
169
170instance Contraction (Vector (Complex Float)) (Vector (Complex Float)) (Complex Float) where
171 (×) = udot
172
173
174-- | alternative function for the matrix product (×)
175mmul :: Contraction a b c => a -> b -> c
176mmul = (×)
177
178--------------------------------------------------------------------------------
179
180class Mul a b c | a b -> c where
181 infixl 7 <>
182 -- | Matrix-matrix, matrix-vector, and vector-matrix products.
183 (<>) :: Product t => a t -> b t -> c t
184
185instance Mul Matrix Matrix Matrix where
186 (<>) = mXm
187
188instance Mul Matrix Vector Vector where
189 (<>) m v = flatten $ m <> asColumn v
190
191instance Mul Vector Matrix Vector where
192 (<>) v m = flatten $ asRow v <> m
193
194--------------------------------------------------------------------------------
195
196class LSDiv c where
197 infixl 7 <\>
198 -- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD)
199 (<\>) :: Field t => Matrix t -> c t -> c t
200
201instance LSDiv Vector where
202 m <\> v = flatten (linearSolveSVD m (reshape 1 v))
203
204instance LSDiv Matrix where
205 (<\>) = linearSolveSVD
206
207--------------------------------------------------------
208
209{- | Dot product : @u · v = 'cdot' u v@
210
211 (unicode 0x00b7, middle dot, Alt-Gr .)
212
213>>> fromList [1,i] · fromList[2*i+1,3]
2141.0 :+ (-1.0)
215
216-}
217(·) :: (Container Vector t, Product t) => Vector t -> Vector t -> t
218infixl 7 ·
219u · v = cdot u v
220
221--------------------------------------------------------------------------------
222
223-- bidirectional type inference
224class Konst e d c | d -> c, c -> d
225 where
226 -- |
227 -- >>> konst 7 3 :: Vector Float
228 -- fromList [7.0,7.0,7.0]
229 --
230 -- >>> konst i (3::Int,4::Int)
231 -- (3><4)
232 -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
233 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
234 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]
235 --
236 konst :: e -> d -> c e
237
238instance Container Vector e => Konst e Int Vector
239 where
240 konst = konst'
241
242instance Container Vector e => Konst e (Int,Int) Matrix
243 where
244 konst = konst'
245
246--------------------------------------------------------------------------------
247
248class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
249 where
250 -- |
251 -- >>> build 5 (**2) :: Vector Double
252 -- fromList [0.0,1.0,4.0,9.0,16.0]
253 --
254 -- Hilbert matrix of order N:
255 --
256 -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
257 -- >>> putStr . dispf 2 $ hilb 3
258 -- 3x3
259 -- 1.00 0.50 0.33
260 -- 0.50 0.33 0.25
261 -- 0.33 0.25 0.20
262 --
263 build :: d -> f -> c e
264
265instance Container Vector e => Build Int (e -> e) Vector e
266 where
267 build = build'
268
269instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e
270 where
271 build = build'
272
273--------------------------------------------------------------------------------
274
275{- | Compute mean vector and covariance matrix of the rows of a matrix.
276
277>>> meanCov $ gaussianSample 666 1000 (fromList[4,5]) (diagl[2,3])
278(fromList [4.010341078059521,5.0197204699640405],
279(2><2)
280 [ 1.9862461923890056, -1.0127225830525157e-2
281 , -1.0127225830525157e-2, 3.0373954915729318 ])
282
283-}
284meanCov :: Matrix Double -> (Vector Double, Matrix Double)
285meanCov x = (med,cov) where
286 r = rows x
287 k = 1 / fromIntegral r
288 med = konst k r `vXm` x
289 meds = konst 1 r `outer` med
290 xc = x `sub` meds
291 cov = scale (recip (fromIntegral (r-1))) (trans xc `mXm` xc)
292
293--------------------------------------------------------------------------------
294
295{-# DEPRECATED dot "use udot" #-}
296dot :: Product e => Vector e -> Vector e -> e
297dot = udot
298
299-- | contraction operator, equivalent to (x)
300infixr 7 <.>
301(<.>) :: Contraction a b c => a -> b -> c
302(<.>) = (×)
303