summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/Container.hs
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base/src/Numeric/Container.hs')
-rw-r--r--packages/base/src/Numeric/Container.hs273
1 files changed, 32 insertions, 241 deletions
diff --git a/packages/base/src/Numeric/Container.hs b/packages/base/src/Numeric/Container.hs
index 067c5fa..6a841aa 100644
--- a/packages/base/src/Numeric/Container.hs
+++ b/packages/base/src/Numeric/Container.hs
@@ -1,258 +1,49 @@
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 : BSD3
13-- Maintainer : Alberto Ruiz
14-- Stability : provisional
15--
16-- Basic numeric operations on 'Vector' and 'Matrix', including conversion routines.
17--
18-- The 'Container' class is used to define optimized generic functions which work
19-- on 'Vector' and 'Matrix' with real or complex elements.
20--
21-- Some of these functions are also available in the instances of the standard
22-- numeric Haskell classes provided by "Numeric.LinearAlgebra".
23--
24-----------------------------------------------------------------------------
25{-# OPTIONS_HADDOCK hide #-} 1{-# OPTIONS_HADDOCK hide #-}
26 2
27module Numeric.Container ( 3module Numeric.Container(
28 -- * Basic functions
29 module Data.Packed, 4 module Data.Packed,
30 konst, build, 5 constant,
31 linspace, 6 linspace,
32 diag, ident, 7 diag,
8 ident,
33 ctrans, 9 ctrans,
34 -- * Generic operations 10 Container(scaleRecip, addConstant,add, sub, mul, divide, equal),
35 Container, 11 scalar,
36 add, mul, sub, divide, equal, scaleRecip, addConstant, 12 conj,
37 scalar, conj, scale, arctan2, cmap, 13 scale,
38 atIndex, minIndex, maxIndex, minElement, maxElement, 14 arctan2,
15 cmap,
16 Konst(..),
17 Build(..),
18 atIndex,
19 minIndex, maxIndex, minElement, maxElement,
39 sumElements, prodElements, 20 sumElements, prodElements,
40 step, cond, find, assoc, accum, 21 step, cond, find, assoc, accum,
41 Transposable(..), Linear(..), 22 Element(..),
42 -- * Matrix product 23 Product(..),
43 Product(..), udot, dot, (◇),
44 Mul(..),
45 Contraction(..),(<.>),
46 optimiseMult, 24 optimiseMult,
47 mXm,mXv,vXm,LSDiv(..), 25 mXm, mXv, vXm, (<.>),
26 Mul(..),
27 LSDiv, (<\>),
48 outer, kronecker, 28 outer, kronecker,
49 -- * Random numbers
50 RandDist(..), 29 RandDist(..),
51 randomVector, 30 randomVector, gaussianSample, uniformSample,
52 gaussianSample, 31 meanCov,
53 uniformSample,
54 -- * Element conversion
55 Convert(..), 32 Convert(..),
56 Complexable(), 33 Complexable,
57 RealElement(), 34 RealElement,
58 35 RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf,
59 RealOf, ComplexOf, SingleOf, DoubleOf,
60
61 IndexOf,
62 module Data.Complex, 36 module Data.Complex,
63 -- * IO 37 dispf, disps, dispcf, vecdisp, latexFormat, format,
64 module Data.Packed.IO, 38 loadMatrix, saveMatrix, readMatrix
65 -- * Misc
66 Testable(..)
67) where 39) where
68 40
69import Data.Packed hiding (stepD, stepF, condD, condF, conjugateC, conjugateQ)
70import Data.Packed.Internal.Numeric
71import Data.Complex
72import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD)
73import Data.Monoid(Monoid(mconcat))
74import Data.Packed.IO
75import Numeric.LinearAlgebra.Random
76
77------------------------------------------------------------------
78
79{- | Creates a real vector containing a range of values:
80
81>>> linspace 5 (-3,7::Double)
82fromList [-3.0,-0.5,2.0,4.5,7.0]@
83
84>>> linspace 5 (8,2+i) :: Vector (Complex Double)
85fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]
86
87Logarithmic spacing can be defined as follows:
88
89@logspace n (a,b) = 10 ** linspace n (a,b)@
90-}
91linspace :: (Container Vector e) => Int -> (e, e) -> Vector e
92linspace 0 (a,b) = fromList[(a+b)/2]
93linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1]
94 where s = (b-a)/fromIntegral (n-1)
95
96--------------------------------------------------------
97
98{- | Matrix product, matrix - vector product, and dot product (equivalent to 'contraction')
99
100(This operator can also be written using the unicode symbol ◇ (25c7).)
101
102Examples:
103
104>>> let a = (3><4) [1..] :: Matrix Double
105>>> let v = fromList [1,0,2,-1] :: Vector Double
106>>> let u = fromList [1,2,3] :: Vector Double
107
108>>> a
109(3><4)
110 [ 1.0, 2.0, 3.0, 4.0
111 , 5.0, 6.0, 7.0, 8.0
112 , 9.0, 10.0, 11.0, 12.0 ]
113
114matrix × matrix:
115
116>>> disp 2 (a <.> trans a)
1173x3
118 30 70 110
119 70 174 278
120110 278 446
121
122matrix × vector:
123
124>>> a <.> v
125fromList [3.0,11.0,19.0]
126
127dot product:
128
129>>> u <.> fromList[3,2,1::Double]
13010
131
132For complex vectors the first argument is conjugated:
133
134>>> fromList [1,i] <.> fromList[2*i+1,3]
1351.0 :+ (-1.0)
136
137>>> fromList [1,i,1-i] <.> complex a
138fromList [10.0 :+ 4.0,12.0 :+ 4.0,14.0 :+ 4.0,16.0 :+ 4.0]
139-}
140infixl 7 <.>
141(<.>) :: Contraction a b c => a -> b -> c
142(<.>) = contraction
143
144 41
145class Contraction a b c | a b -> c 42import Data.Packed.Numeric
146 where 43import Data.Packed
147 -- | Matrix product, matrix - vector product, and dot product 44import Data.Packed.Internal(constantD)
148 contraction :: a -> b -> c 45import Data.Complex
149
150instance (Product t, Container Vector t) => Contraction (Vector t) (Vector t) t where
151 u `contraction` v = conj u `udot` v
152
153instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
154 contraction = mXv
155
156instance (Container Vector t, Product t) => Contraction (Vector t) (Matrix t) (Vector t) where
157 contraction v m = (conj v) `vXm` m
158
159instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where
160 contraction = mXm
161
162
163--------------------------------------------------------------------------------
164
165class Mul a b c | a b -> c where
166 infixl 7 <>
167 -- | Matrix-matrix, matrix-vector, and vector-matrix products.
168 (<>) :: Product t => a t -> b t -> c t
169
170instance Mul Matrix Matrix Matrix where
171 (<>) = mXm
172
173instance Mul Matrix Vector Vector where
174 (<>) m v = flatten $ m <> asColumn v
175
176instance Mul Vector Matrix Vector where
177 (<>) v m = flatten $ asRow v <> m
178
179--------------------------------------------------------------------------------
180
181class LSDiv c where
182 infixl 7 <\>
183 -- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD)
184 (<\>) :: Field t => Matrix t -> c t -> c t
185
186instance LSDiv Vector where
187 m <\> v = flatten (linearSolveSVD m (reshape 1 v))
188
189instance LSDiv Matrix where
190 (<\>) = linearSolveSVD
191
192--------------------------------------------------------------------------------
193
194class Konst e d c | d -> c, c -> d
195 where
196 -- |
197 -- >>> konst 7 3 :: Vector Float
198 -- fromList [7.0,7.0,7.0]
199 --
200 -- >>> konst i (3::Int,4::Int)
201 -- (3><4)
202 -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
203 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
204 -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]
205 --
206 konst :: e -> d -> c e
207
208instance Container Vector e => Konst e Int Vector
209 where
210 konst = konst'
211
212instance Container Vector e => Konst e (Int,Int) Matrix
213 where
214 konst = konst'
215
216--------------------------------------------------------------------------------
217
218class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
219 where
220 -- |
221 -- >>> build 5 (**2) :: Vector Double
222 -- fromList [0.0,1.0,4.0,9.0,16.0]
223 --
224 -- Hilbert matrix of order N:
225 --
226 -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double
227 -- >>> putStr . dispf 2 $ hilb 3
228 -- 3x3
229 -- 1.00 0.50 0.33
230 -- 0.50 0.33 0.25
231 -- 0.33 0.25 0.20
232 --
233 build :: d -> f -> c e
234
235instance Container Vector e => Build Int (e -> e) Vector e
236 where
237 build = build'
238
239instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e
240 where
241 build = build'
242
243--------------------------------------------------------------------------------
244
245-- | alternative unicode symbol (25c7) for 'contraction'
246(◇) :: Contraction a b c => a -> b -> c
247infixl 7 ◇
248(◇) = contraction
249
250-- | dot product: @cdot u v = 'udot' ('conj' u) v@
251dot :: (Container Vector t, Product t) => Vector t -> Vector t -> t
252dot u v = udot (conj u) v
253
254--------------------------------------------------------------------------------
255 46
256optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t 47constant :: Element a => a -> Int -> Vector a
257optimiseMult = mconcat 48constant = constantD
258 49