summaryrefslogtreecommitdiff
path: root/lib/GSLHaskell.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/GSLHaskell.hs')
-rw-r--r--lib/GSLHaskell.hs501
1 files changed, 501 insertions, 0 deletions
diff --git a/lib/GSLHaskell.hs b/lib/GSLHaskell.hs
new file mode 100644
index 0000000..e65ff28
--- /dev/null
+++ b/lib/GSLHaskell.hs
@@ -0,0 +1,501 @@
1{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-}
2-----------------------------------------------------------------------------
3{- |
4Module : GSLHaskell
5Copyright : (c) Alberto Ruiz 2006
6License : GPL-style
7
8Maintainer : Alberto Ruiz (aruiz at um dot es)
9Stability : provisional
10Portability : uses -fffi and -fglasgow-exts
11
12GSLHaskell interface, with reasonable numeric instances for Vectors and Matrices. In the context of the standard numeric operators, one-component vectors and matrices automatically expand to match the dimensions of the other operand.
13
14-}
15-----------------------------------------------------------------------------
16
17module GSLHaskell(
18 module Data.Packed.Vector,
19 module Data.Packed.Matrix,
20 module LinearAlgebra.Algorithms,
21 module LAPACK,
22 module GSL.Integration,
23 module GSL.Differentiation,
24 module GSL.Fourier,
25 module GSL.Polynomials,
26 module GSL.Minimization,
27 module GSL.Matrix,
28 module GSL.Special,
29 module Graphics.Plot,
30 module Complex,
31 Mul,(<>), readMatrix, size, dispR, dispC, format, gmap, Joinable, (<|>),(<->), GSLHaskell.constant,
32 fromArray2D, fromComplex, toComplex, GSLHaskell.pnorm, scale, outer
33) where
34
35
36import LAPACK
37import GSL.Integration
38import GSL.Differentiation
39import GSL.Fourier
40import GSL.Polynomials
41import GSL.Minimization
42import GSL.Matrix
43import Graphics.Plot
44import Complex
45import GSL.Special(setErrorHandlerOff,
46 erf,
47 erf_Z,
48 bessel_J0_e,
49 exp_e10_e,
50 gamma)
51import Data.Packed.Internal hiding (dsp)
52import Data.Packed.Vector hiding (constant)
53import Data.Packed.Matrix
54import Data.Packed.Matrix hiding ((><))
55import GSL.Vector
56import LinearAlgebra.Linear
57import qualified LinearAlgebra.Algorithms
58import LinearAlgebra.Algorithms hiding (pnorm)
59import Complex
60import Numeric(showGFloat)
61import Data.List(transpose,intersperse)
62import Foreign(Storable)
63import Data.Array
64
65
66adaptScalar f1 f2 f3 x y
67 | dim x == 1 = f1 (x@>0) y
68 | dim y == 1 = f3 x (y@>0)
69 | otherwise = f2 x y
70
71liftMatrix2' :: (Field t, Field a, Field b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t
72liftMatrix2' f m1 m2 | compat' m1 m2 = reshape (max (cols m1) (cols m2)) (f (cdat m1) (cdat m2))
73 | otherwise = error "nonconformant matrices in liftMatrix2'"
74
75compat' :: Matrix a -> Matrix b -> Bool
76compat' m1 m2 = rows m1 == 1 && cols m1 == 1
77 || rows m2 == 1 && cols m2 == 1
78 || rows m1 == rows m2 && cols m1 == cols m2
79
80instance (Eq a, Field a) => Eq (Vector a) where
81 a == b = dim a == dim b && toList a == toList b
82
83instance (Linear Vector a) => Num (Vector a) where
84 (+) = adaptScalar addConstant add (flip addConstant)
85 negate = scale (-1)
86 (*) = adaptScalar scale mul (flip scale)
87 signum = liftVector signum
88 abs = liftVector abs
89 fromInteger = fromList . return . fromInteger
90
91instance (Eq a, Field a) => Eq (Matrix a) where
92 a == b = rows a == rows b && cols a == cols b && cdat a == cdat b && fdat a == fdat b
93
94instance (Field a, Linear Vector a) => Num (Matrix a) where
95 (+) = liftMatrix2' (+)
96 (-) = liftMatrix2' (-)
97 negate = liftMatrix negate
98 (*) = liftMatrix2' (*)
99 signum = liftMatrix signum
100 abs = liftMatrix abs
101 fromInteger = (1><1) . return . fromInteger
102
103---------------------------------------------------
104
105instance Fractional (Vector Double) where
106 fromRational n = fromList [fromRational n]
107 (/) = adaptScalar f (vectorZipR Div) g where
108 r `f` v = vectorMapValR Recip r v
109 v `g` r = scale (recip r) v
110
111-------------------------------------------------------
112
113instance Fractional (Vector (Complex Double)) where
114 fromRational n = fromList [fromRational n]
115 (/) = adaptScalar f (vectorZipC Div) g where
116 r `f` v = vectorMapValC Recip r v
117 v `g` r = scale (recip r) v
118
119------------------------------------------------------
120
121instance Fractional (Matrix Double) where
122 fromRational n = (1><1) [fromRational n]
123 (/) = liftMatrix2' (/)
124
125-------------------------------------------------------
126
127instance Fractional (Matrix (Complex Double)) where
128 fromRational n = (1><1) [fromRational n]
129 (/) = liftMatrix2' (/)
130
131---------------------------------------------------------
132
133instance Floating (Vector Double) where
134 sin = vectorMapR Sin
135 cos = vectorMapR Cos
136 tan = vectorMapR Tan
137 asin = vectorMapR ASin
138 acos = vectorMapR ACos
139 atan = vectorMapR ATan
140 sinh = vectorMapR Sinh
141 cosh = vectorMapR Cosh
142 tanh = vectorMapR Tanh
143 asinh = vectorMapR ASinh
144 acosh = vectorMapR ACosh
145 atanh = vectorMapR ATanh
146 exp = vectorMapR Exp
147 log = vectorMapR Log
148 sqrt = vectorMapR Sqrt
149 (**) = adaptScalar (vectorMapValR PowSV) (vectorZipR Pow) (flip (vectorMapValR PowVS))
150 pi = fromList [pi]
151
152-----------------------------------------------------------
153
154instance Floating (Matrix Double) where
155 sin = liftMatrix sin
156 cos = liftMatrix cos
157 tan = liftMatrix tan
158 asin = liftMatrix asin
159 acos = liftMatrix acos
160 atan = liftMatrix atan
161 sinh = liftMatrix sinh
162 cosh = liftMatrix cosh
163 tanh = liftMatrix tanh
164 asinh = liftMatrix asinh
165 acosh = liftMatrix acosh
166 atanh = liftMatrix atanh
167 exp = liftMatrix exp
168 log = liftMatrix log
169 (**) = liftMatrix2' (**)
170 sqrt = liftMatrix sqrt
171 pi = (1><1) [pi]
172-------------------------------------------------------------
173
174instance Floating (Vector (Complex Double)) where
175 sin = vectorMapC Sin
176 cos = vectorMapC Cos
177 tan = vectorMapC Tan
178 asin = vectorMapC ASin
179 acos = vectorMapC ACos
180 atan = vectorMapC ATan
181 sinh = vectorMapC Sinh
182 cosh = vectorMapC Cosh
183 tanh = vectorMapC Tanh
184 asinh = vectorMapC ASinh
185 acosh = vectorMapC ACosh
186 atanh = vectorMapC ATanh
187 exp = vectorMapC Exp
188 log = vectorMapC Log
189 sqrt = vectorMapC Sqrt
190 (**) = adaptScalar (vectorMapValC PowSV) (vectorZipC Pow) (flip (vectorMapValC PowVS))
191 pi = fromList [pi]
192
193---------------------------------------------------------------
194
195instance Floating (Matrix (Complex Double)) where
196 sin = liftMatrix sin
197 cos = liftMatrix cos
198 tan = liftMatrix tan
199 asin = liftMatrix asin
200 acos = liftMatrix acos
201 atan = liftMatrix atan
202 sinh = liftMatrix sinh
203 cosh = liftMatrix cosh
204 tanh = liftMatrix tanh
205 asinh = liftMatrix asinh
206 acosh = liftMatrix acosh
207 atanh = liftMatrix atanh
208 exp = liftMatrix exp
209 log = liftMatrix log
210 (**) = liftMatrix2' (**)
211 sqrt = liftMatrix sqrt
212 pi = (1><1) [pi]
213
214---------------------------------------------------------------
215
216
217class Mul a b c | a b -> c where
218 infixl 7 <>
219{- | An overloaded operator for matrix products, matrix-vector and vector-matrix products, dot products and scaling of vectors and matrices. Type consistency is statically checked. Alternatively, you can use the specific functions described below, but using this operator you can automatically combine real and complex objects.
220
221@v = 'fromList' [1,2,3] :: Vector Double
222cv = 'fromList' [1+'i',2]
223m = 'fromLists' [[1,2,3],
224 [4,5,7]] :: Matrix Double
225cm = 'fromLists' [[ 1, 2],
226 [3+'i',7*'i'],
227 [ 'i', 1]]
228\
229\> m \<\> v
23014. 35.
231\
232\> cv \<\> m
2339.+1.i 12.+2.i 17.+3.i
234\
235\> m \<\> cm
236 7.+5.i 5.+14.i
23719.+12.i 15.+35.i
238\
239\> v \<\> 'i'
2401.i 2.i 3.i
241\
242\> v \<\> v
24314.0
244\
245\> cv \<\> cv
2464.0 :+ 2.0@
247
248-}
249 (<>) :: a -> b -> c
250
251
252instance Mul Double Double Double where
253 (<>) = (*)
254
255instance Mul Double (Complex Double) (Complex Double) where
256 a <> b = (a:+0) * b
257
258instance Mul (Complex Double) Double (Complex Double) where
259 a <> b = a * (b:+0)
260
261instance Mul (Complex Double) (Complex Double) (Complex Double) where
262 (<>) = (*)
263
264--------------------------------- matrix matrix
265
266instance Mul (Matrix Double) (Matrix Double) (Matrix Double) where
267 (<>) = multiply
268
269instance Mul (Matrix (Complex Double)) (Matrix (Complex Double)) (Matrix (Complex Double)) where
270 (<>) = multiply
271
272instance Mul (Matrix (Complex Double)) (Matrix Double) (Matrix (Complex Double)) where
273 c <> r = c <> liftMatrix comp r
274
275instance Mul (Matrix Double) (Matrix (Complex Double)) (Matrix (Complex Double)) where
276 r <> c = liftMatrix comp r <> c
277
278--------------------------------- (Matrix Double) (Vector Double)
279
280instance Mul (Matrix Double) (Vector Double) (Vector Double) where
281 (<>) = mXv
282
283instance Mul (Matrix (Complex Double)) (Vector (Complex Double)) (Vector (Complex Double)) where
284 (<>) = mXv
285
286instance Mul (Matrix (Complex Double)) (Vector Double) (Vector (Complex Double)) where
287 m <> v = m <> comp v
288
289instance Mul (Matrix Double) (Vector (Complex Double)) (Vector (Complex Double)) where
290 m <> v = liftMatrix comp m <> v
291
292--------------------------------- (Vector Double) (Matrix Double)
293
294instance Mul (Vector Double) (Matrix Double) (Vector Double) where
295 (<>) = vXm
296
297instance Mul (Vector (Complex Double)) (Matrix (Complex Double)) (Vector (Complex Double)) where
298 (<>) = vXm
299
300instance Mul (Vector (Complex Double)) (Matrix Double) (Vector (Complex Double)) where
301 v <> m = v <> liftMatrix comp m
302
303instance Mul (Vector Double) (Matrix (Complex Double)) (Vector (Complex Double)) where
304 v <> m = comp v <> m
305
306--------------------------------- dot product
307
308instance Mul (Vector Double) (Vector Double) Double where
309 (<>) = dot
310
311instance Mul (Vector (Complex Double)) (Vector (Complex Double)) (Complex Double) where
312 (<>) = dot
313
314instance Mul (Vector Double) (Vector (Complex Double)) (Complex Double) where
315 a <> b = comp a <> b
316
317instance Mul (Vector (Complex Double)) (Vector Double) (Complex Double) where
318 (<>) = flip (<>)
319
320--------------------------------- scaling vectors
321
322instance Mul Double (Vector Double) (Vector Double) where
323 (<>) = scale
324
325instance Mul (Vector Double) Double (Vector Double) where
326 (<>) = flip (<>)
327
328instance Mul (Complex Double) (Vector (Complex Double)) (Vector (Complex Double)) where
329 (<>) = scale
330
331instance Mul (Vector (Complex Double)) (Complex Double) (Vector (Complex Double)) where
332 (<>) = flip (<>)
333
334instance Mul Double (Vector (Complex Double)) (Vector (Complex Double)) where
335 a <> v = (a:+0) <> v
336
337instance Mul (Vector (Complex Double)) Double (Vector (Complex Double)) where
338 (<>) = flip (<>)
339
340instance Mul (Complex Double) (Vector Double) (Vector (Complex Double)) where
341 a <> v = a <> comp v
342
343instance Mul (Vector Double) (Complex Double) (Vector (Complex Double)) where
344 (<>) = flip (<>)
345
346--------------------------------- scaling matrices
347
348instance Mul Double (Matrix Double) (Matrix Double) where
349 (<>) a = liftMatrix (a <>)
350
351instance Mul (Matrix Double) Double (Matrix Double) where
352 (<>) = flip (<>)
353
354instance Mul (Complex Double) (Matrix (Complex Double)) (Matrix (Complex Double)) where
355 (<>) a = liftMatrix (a <>)
356
357instance Mul (Matrix (Complex Double)) (Complex Double) (Matrix (Complex Double)) where
358 (<>) = flip (<>)
359
360instance Mul Double (Matrix (Complex Double)) (Matrix (Complex Double)) where
361 a <> m = (a:+0) <> m
362
363instance Mul (Matrix (Complex Double)) Double (Matrix (Complex Double)) where
364 (<>) = flip (<>)
365
366instance Mul (Complex Double) (Matrix Double) (Matrix (Complex Double)) where
367 a <> m = a <> liftMatrix comp m
368
369instance Mul (Matrix Double) (Complex Double) (Matrix (Complex Double)) where
370 (<>) = flip (<>)
371
372-----------------------------------------------------------------------------------
373
374size :: Vector a -> Int
375size = dim
376
377gmap :: (Storable a, Storable b) => (a->b) -> Vector a -> Vector b
378gmap f v = liftVector f v
379
380constant :: Double -> Int -> Vector Double
381constant = constantR
382
383-- shows a Double with n digits after the decimal point
384shf :: (RealFloat a) => Int -> a -> String
385shf dec n | abs n < 1e-10 = "0."
386 | abs (n - (fromIntegral.round $ n)) < 1e-10 = show (round n) ++"."
387 | otherwise = showGFloat (Just dec) n ""
388-- shows a Complex Double as a pair, with n digits after the decimal point
389shfc n z@ (a:+b)
390 | magnitude z <1e-10 = "0."
391 | abs b < 1e-10 = shf n a
392 | abs a < 1e-10 = shf n b ++"i"
393 | b > 0 = shf n a ++"+"++shf n b ++"i"
394 | otherwise = shf n a ++shf n b ++"i"
395
396dsp :: String -> [[String]] -> String
397dsp sep as = unlines . map unwords' $ transpose mtp where
398 mt = transpose as
399 longs = map (maximum . map length) mt
400 mtp = zipWith (\a b -> map (pad a) b) longs mt
401 pad n str = replicate (n - length str) ' ' ++ str
402 unwords' = concat . intersperse sep
403
404format :: (Field t) => String -> (t -> String) -> Matrix t -> String
405format sep f m = dsp sep . map (map f) . toLists $ m
406
407disp m f = putStrLn $ "matrix ("++show (rows m) ++"x"++ show (cols m) ++")\n"++format " | " f m
408
409dispR :: Int -> Matrix Double -> IO ()
410dispR d m = disp m (shf d)
411
412dispC :: Int -> Matrix (Complex Double) -> IO ()
413dispC d m = disp m (shfc d)
414
415-- | creates a matrix from a table of numbers.
416readMatrix :: String -> Matrix Double
417readMatrix = fromLists . map (map read). map words . filter (not.null) . lines
418
419-------------------------------------------------------------
420
421class Joinable a b c | a b -> c where
422 joinH :: a -> b -> c
423 joinV :: a -> b -> c
424
425instance Joinable (Matrix Double) (Vector Double) (Matrix Double) where
426 joinH m v = fromBlocks [[m,reshape 1 v]]
427 joinV m v = fromBlocks [[m],[reshape (size v) v]]
428
429instance Joinable (Vector Double) (Matrix Double) (Matrix Double) where
430 joinH v m = fromBlocks [[reshape 1 v,m]]
431 joinV v m = fromBlocks [[reshape (size v) v],[m]]
432
433instance Joinable (Matrix Double) (Matrix Double) (Matrix Double) where
434 joinH m1 m2 = fromBlocks [[m1,m2]]
435 joinV m1 m2 = fromBlocks [[m1],[m2]]
436
437instance Joinable (Matrix (Complex Double)) (Vector (Complex Double)) (Matrix (Complex Double)) where
438 joinH m v = fromBlocks [[m,reshape 1 v]]
439 joinV m v = fromBlocks [[m],[reshape (size v) v]]
440
441instance Joinable (Vector (Complex Double)) (Matrix (Complex Double)) (Matrix (Complex Double)) where
442 joinH v m = fromBlocks [[reshape 1 v,m]]
443 joinV v m = fromBlocks [[reshape (size v) v],[m]]
444
445instance Joinable (Matrix (Complex Double)) (Matrix (Complex Double)) (Matrix (Complex Double)) where
446 joinH m1 m2 = fromBlocks [[m1,m2]]
447 joinV m1 m2 = fromBlocks [[m1],[m2]]
448
449infixl 3 <|>, <->
450
451{- | Horizontal concatenation of matrices and vectors:
452
453@\> 'ident' 3 \<-\> i\<\>'ident' 3 \<|\> 'fromList' [1..6]
454 1. 0. 0. 1.
455 0. 1. 0. 2.
456 0. 0. 1. 3.
4571.i 0. 0. 4.
458 0. 1.i 0. 5.
459 0. 0. 1.i 6.@
460-}
461(<|>) :: (Joinable a b c) => a -> b -> c
462a <|> b = joinH a b
463
464-- | Vertical concatenation of matrices and vectors.
465(<->) :: (Joinable a b c) => a -> b -> c
466a <-> b = joinV a b
467
468----------------------------------------------------------
469
470fromArray2D :: (Field e) => Array (Int, Int) e -> Matrix e
471fromArray2D m = (r><c) (elems m)
472 where ((r0,c0),(r1,c1)) = bounds m
473 r = r1-r0+1
474 c = c1-c0+1
475
476-- | creates a complex vector from vectors with real and imaginary parts
477toComplexV :: (Vector Double, Vector Double) -> Vector (Complex Double)
478toComplexV (r,i) = asComplex $ flatten $ fromColumns [r,i]
479
480-- | extracts the real and imaginary parts of a complex vector
481fromComplexV :: Vector (Complex Double) -> (Vector Double, Vector Double)
482fromComplexV m = (a,b) where [a,b] = toColumns $ reshape 2 $ asReal m
483
484-- | creates a complex matrix from matrices with real and imaginary parts
485toComplexM :: (Matrix Double, Matrix Double) -> Matrix (Complex Double)
486toComplexM (r,i) = reshape (cols r) $ asComplex $ flatten $ fromColumns [flatten r, flatten i]
487
488-- | extracts the real and imaginary parts of a complex matrix
489fromComplexM :: Matrix (Complex Double) -> (Matrix Double, Matrix Double)
490fromComplexM m = (reshape c a, reshape c b)
491 where c = cols m
492 [a,b] = toColumns $ reshape 2 $ asReal $ flatten m
493
494fromComplex :: Matrix (Complex Double) -> (Matrix Double, Matrix Double)
495fromComplex = fromComplexM
496
497
498pnorm :: (Normed t1, Num t) => t -> t1 -> Double
499pnorm 0 = LinearAlgebra.Algorithms.pnorm Infinity
500pnorm 1 = LinearAlgebra.Algorithms.pnorm PNorm1
501pnorm 2 = LinearAlgebra.Algorithms.pnorm PNorm2 \ No newline at end of file