diff options
Diffstat (limited to 'packages/base/src/Numeric/Container.hs')
-rw-r--r-- | packages/base/src/Numeric/Container.hs | 240 |
1 files changed, 0 insertions, 240 deletions
diff --git a/packages/base/src/Numeric/Container.hs b/packages/base/src/Numeric/Container.hs deleted file mode 100644 index 240e5f5..0000000 --- a/packages/base/src/Numeric/Container.hs +++ /dev/null | |||
@@ -1,240 +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 : 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 #-} | ||
26 | |||
27 | module Numeric.Container ( | ||
28 | -- * Basic functions | ||
29 | module Data.Packed, | ||
30 | konst, build, | ||
31 | linspace, | ||
32 | diag, ident, | ||
33 | ctrans, | ||
34 | -- * Generic operations | ||
35 | Container(..), | ||
36 | -- * Matrix product | ||
37 | Product(..), udot, dot, (◇), | ||
38 | Mul(..), | ||
39 | Contraction(..), | ||
40 | optimiseMult, | ||
41 | mXm,mXv,vXm,LSDiv(..), | ||
42 | outer, kronecker, | ||
43 | -- * Element conversion | ||
44 | Convert(..), | ||
45 | Complexable(), | ||
46 | RealElement(), | ||
47 | |||
48 | RealOf, ComplexOf, SingleOf, DoubleOf, | ||
49 | |||
50 | IndexOf, | ||
51 | module Data.Complex | ||
52 | ) where | ||
53 | |||
54 | import Data.Packed hiding (stepD, stepF, condD, condF, conjugateC, conjugateQ) | ||
55 | import Data.Packed.Numeric | ||
56 | import Data.Complex | ||
57 | import Numeric.LinearAlgebra.Algorithms(Field,linearSolveSVD) | ||
58 | import Data.Monoid(Monoid(mconcat)) | ||
59 | |||
60 | ------------------------------------------------------------------ | ||
61 | |||
62 | {- | Creates a real vector containing a range of values: | ||
63 | |||
64 | >>> linspace 5 (-3,7::Double) | ||
65 | fromList [-3.0,-0.5,2.0,4.5,7.0]@ | ||
66 | |||
67 | >>> linspace 5 (8,2+i) :: Vector (Complex Double) | ||
68 | fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0] | ||
69 | |||
70 | Logarithmic spacing can be defined as follows: | ||
71 | |||
72 | @logspace n (a,b) = 10 ** linspace n (a,b)@ | ||
73 | -} | ||
74 | linspace :: (Container Vector e) => Int -> (e, e) -> Vector e | ||
75 | linspace 0 (a,b) = fromList[(a+b)/2] | ||
76 | linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1] | ||
77 | where s = (b-a)/fromIntegral (n-1) | ||
78 | |||
79 | -------------------------------------------------------- | ||
80 | |||
81 | class Contraction a b c | a b -> c | ||
82 | where | ||
83 | infixl 7 <.> | ||
84 | {- | Matrix product, matrix vector product, and dot product | ||
85 | |||
86 | Examples: | ||
87 | |||
88 | >>> let a = (3><4) [1..] :: Matrix Double | ||
89 | >>> let v = fromList [1,0,2,-1] :: Vector Double | ||
90 | >>> let u = fromList [1,2,3] :: Vector Double | ||
91 | |||
92 | >>> a | ||
93 | (3><4) | ||
94 | [ 1.0, 2.0, 3.0, 4.0 | ||
95 | , 5.0, 6.0, 7.0, 8.0 | ||
96 | , 9.0, 10.0, 11.0, 12.0 ] | ||
97 | |||
98 | matrix × matrix: | ||
99 | |||
100 | >>> disp 2 (a <.> trans a) | ||
101 | 3x3 | ||
102 | 30 70 110 | ||
103 | 70 174 278 | ||
104 | 110 278 446 | ||
105 | |||
106 | matrix × vector: | ||
107 | |||
108 | >>> a <.> v | ||
109 | fromList [3.0,11.0,19.0] | ||
110 | |||
111 | dot product: | ||
112 | |||
113 | >>> u <.> fromList[3,2,1::Double] | ||
114 | 10 | ||
115 | |||
116 | For complex vectors the first argument is conjugated: | ||
117 | |||
118 | >>> fromList [1,i] <.> fromList[2*i+1,3] | ||
119 | 1.0 :+ (-1.0) | ||
120 | |||
121 | >>> fromList [1,i,1-i] <.> complex a | ||
122 | fromList [10.0 :+ 4.0,12.0 :+ 4.0,14.0 :+ 4.0,16.0 :+ 4.0] | ||
123 | |||
124 | -} | ||
125 | (<.>) :: a -> b -> c | ||
126 | |||
127 | |||
128 | instance (Product t, Container Vector t) => Contraction (Vector t) (Vector t) t where | ||
129 | u <.> v = conj u `udot` v | ||
130 | |||
131 | instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where | ||
132 | (<.>) = mXv | ||
133 | |||
134 | instance (Container Vector t, Product t) => Contraction (Vector t) (Matrix t) (Vector t) where | ||
135 | (<.>) v m = (conj v) `vXm` m | ||
136 | |||
137 | instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where | ||
138 | (<.>) = mXm | ||
139 | |||
140 | |||
141 | -------------------------------------------------------------------------------- | ||
142 | |||
143 | class Mul a b c | a b -> c where | ||
144 | infixl 7 <> | ||
145 | -- | Matrix-matrix, matrix-vector, and vector-matrix products. | ||
146 | (<>) :: Product t => a t -> b t -> c t | ||
147 | |||
148 | instance Mul Matrix Matrix Matrix where | ||
149 | (<>) = mXm | ||
150 | |||
151 | instance Mul Matrix Vector Vector where | ||
152 | (<>) m v = flatten $ m <> asColumn v | ||
153 | |||
154 | instance Mul Vector Matrix Vector where | ||
155 | (<>) v m = flatten $ asRow v <> m | ||
156 | |||
157 | -------------------------------------------------------------------------------- | ||
158 | |||
159 | class LSDiv c where | ||
160 | infixl 7 <\> | ||
161 | -- | least squares solution of a linear system, similar to the \\ operator of Matlab\/Octave (based on linearSolveSVD) | ||
162 | (<\>) :: Field t => Matrix t -> c t -> c t | ||
163 | |||
164 | instance LSDiv Vector where | ||
165 | m <\> v = flatten (linearSolveSVD m (reshape 1 v)) | ||
166 | |||
167 | instance LSDiv Matrix where | ||
168 | (<\>) = linearSolveSVD | ||
169 | |||
170 | -------------------------------------------------------------------------------- | ||
171 | |||
172 | class Konst e d c | d -> c, c -> d | ||
173 | where | ||
174 | -- | | ||
175 | -- >>> konst 7 3 :: Vector Float | ||
176 | -- fromList [7.0,7.0,7.0] | ||
177 | -- | ||
178 | -- >>> konst i (3::Int,4::Int) | ||
179 | -- (3><4) | ||
180 | -- [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 | ||
181 | -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 | ||
182 | -- , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ] | ||
183 | -- | ||
184 | konst :: e -> d -> c e | ||
185 | |||
186 | instance Container Vector e => Konst e Int Vector | ||
187 | where | ||
188 | konst = konst' | ||
189 | |||
190 | instance Container Vector e => Konst e (Int,Int) Matrix | ||
191 | where | ||
192 | konst = konst' | ||
193 | |||
194 | -------------------------------------------------------------------------------- | ||
195 | |||
196 | class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f | ||
197 | where | ||
198 | -- | | ||
199 | -- >>> build 5 (**2) :: Vector Double | ||
200 | -- fromList [0.0,1.0,4.0,9.0,16.0] | ||
201 | -- | ||
202 | -- Hilbert matrix of order N: | ||
203 | -- | ||
204 | -- >>> let hilb n = build (n,n) (\i j -> 1/(i+j+1)) :: Matrix Double | ||
205 | -- >>> putStr . dispf 2 $ hilb 3 | ||
206 | -- 3x3 | ||
207 | -- 1.00 0.50 0.33 | ||
208 | -- 0.50 0.33 0.25 | ||
209 | -- 0.33 0.25 0.20 | ||
210 | -- | ||
211 | build :: d -> f -> c e | ||
212 | |||
213 | instance Container Vector e => Build Int (e -> e) Vector e | ||
214 | where | ||
215 | build = build' | ||
216 | |||
217 | instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e | ||
218 | where | ||
219 | build = build' | ||
220 | |||
221 | -------------------------------------------------------------------------------- | ||
222 | |||
223 | {- | alternative operator for '(\<.\>)' | ||
224 | |||
225 | x25c7, white diamond | ||
226 | |||
227 | -} | ||
228 | (◇) :: Contraction a b c => a -> b -> c | ||
229 | infixl 7 ◇ | ||
230 | (◇) = (<.>) | ||
231 | |||
232 | -- | dot product: @cdot u v = 'udot' ('conj' u) v@ | ||
233 | dot :: (Container Vector t, Product t) => Vector t -> Vector t -> t | ||
234 | dot u v = udot (conj u) v | ||
235 | |||
236 | -------------------------------------------------------------------------------- | ||
237 | |||
238 | optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t | ||
239 | optimiseMult = mconcat | ||
240 | |||