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