summaryrefslogtreecommitdiff
path: root/lib/GSL
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2007-06-25 17:34:09 +0000
committerAlberto Ruiz <aruiz@um.es>2007-06-25 17:34:09 +0000
commit2984d5cc1cedb1621f6fa8d9dda0c515441f92e1 (patch)
tree85e155bd77644c26e265996f9cfecd7de70e2450 /lib/GSL
parent1871acb835b4fc164bcff3f6e7467884b87fbd0f (diff)
old tests passed
Diffstat (limited to 'lib/GSL')
-rw-r--r--lib/GSL/Compat.hs370
-rw-r--r--lib/GSL/Minimization.hs8
2 files changed, 375 insertions, 3 deletions
diff --git a/lib/GSL/Compat.hs b/lib/GSL/Compat.hs
new file mode 100644
index 0000000..6a94191
--- /dev/null
+++ b/lib/GSL/Compat.hs
@@ -0,0 +1,370 @@
1{-# OPTIONS_GHC -fglasgow-exts #-}
2-----------------------------------------------------------------------------
3{- |
4Module : GSL.Compat
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
12Creates 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 GSL.Compat(
18 Mul,(<>), fromFile, readMatrix, size, dispR, dispC, format, gmap
19) where
20
21import Data.Packed.Internal hiding (dsp)
22import Data.Packed.Vector
23import Data.Packed.Matrix
24import GSL.Vector
25import GSL.Matrix
26import LinearAlgebra.Algorithms
27import Complex
28import Numeric(showGFloat)
29import Data.List(transpose,intersperse)
30
31
32adaptScalar f1 f2 f3 x y
33 | dim x == 1 = f1 (x@>0) y
34 | dim y == 1 = f3 x (y@>0)
35 | otherwise = f2 x y
36
37instance (Eq a, Field a) => Eq (Vector a) where
38 a == b = dim a == dim b && toList a == toList b
39
40instance (Num a, Field a) => Num (Vector a) where
41 (+) = adaptScalar addConstant add (flip addConstant)
42 negate = scale (-1)
43 (*) = adaptScalar scale mul (flip scale)
44 signum = liftVector signum
45 abs = liftVector abs
46 fromInteger = fromList . return . fromInteger
47
48instance (Eq a, Field a) => Eq (Matrix a) where
49 a == b = rows a == rows b && cols a == cols b && cdat a == cdat b && fdat a == fdat b
50
51instance (Num a, Field a) => Num (Matrix a) where
52 (+) = liftMatrix2 (+)
53 negate = liftMatrix negate
54 (*) = liftMatrix2 (*)
55 signum = liftMatrix signum
56 abs = liftMatrix abs
57 fromInteger = (1><1) . return . fromInteger
58
59---------------------------------------------------
60
61instance Fractional (Vector Double) where
62 fromRational n = fromList [fromRational n]
63 (/) = adaptScalar f (vectorZipR Div) g where
64 r `f` v = vectorMapValR Recip r v
65 v `g` r = scale (recip r) v
66
67-------------------------------------------------------
68
69instance Fractional (Vector (Complex Double)) where
70 fromRational n = fromList [fromRational n]
71 (/) = adaptScalar f (vectorZipC Div) g where
72 r `f` v = vectorMapValC Recip r v
73 v `g` r = scale (recip r) v
74
75------------------------------------------------------
76
77instance Fractional (Matrix Double) where
78 fromRational n = (1><1) [fromRational n]
79 (/) = liftMatrix2 (/)
80
81-------------------------------------------------------
82
83instance Fractional (Matrix (Complex Double)) where
84 fromRational n = (1><1) [fromRational n]
85 (/) = liftMatrix2 (/)
86
87---------------------------------------------------------
88
89instance Floating (Vector Double) where
90 sin = vectorMapR Sin
91 cos = vectorMapR Cos
92 tan = vectorMapR Tan
93 asin = vectorMapR ASin
94 acos = vectorMapR ACos
95 atan = vectorMapR ATan
96 sinh = vectorMapR Sinh
97 cosh = vectorMapR Cosh
98 tanh = vectorMapR Tanh
99 asinh = vectorMapR ASinh
100 acosh = vectorMapR ACosh
101 atanh = vectorMapR ATanh
102 exp = vectorMapR Exp
103 log = vectorMapR Log
104 sqrt = vectorMapR Sqrt
105 (**) = adaptScalar (vectorMapValR PowSV) (vectorZipR Pow) (flip (vectorMapValR PowVS))
106 pi = fromList [pi]
107
108-----------------------------------------------------------
109
110instance Floating (Matrix Double) where
111 sin = liftMatrix sin
112 cos = liftMatrix cos
113 tan = liftMatrix tan
114 asin = liftMatrix asin
115 acos = liftMatrix acos
116 atan = liftMatrix atan
117 sinh = liftMatrix sinh
118 cosh = liftMatrix cosh
119 tanh = liftMatrix tanh
120 asinh = liftMatrix asinh
121 acosh = liftMatrix acosh
122 atanh = liftMatrix atanh
123 exp = liftMatrix exp
124 log = liftMatrix log
125 (**) = liftMatrix2 (**)
126 sqrt = liftMatrix sqrt
127 pi = (1><1) [pi]
128-------------------------------------------------------------
129
130instance Floating (Vector (Complex Double)) where
131 sin = vectorMapC Sin
132 cos = vectorMapC Cos
133 tan = vectorMapC Tan
134 asin = vectorMapC ASin
135 acos = vectorMapC ACos
136 atan = vectorMapC ATan
137 sinh = vectorMapC Sinh
138 cosh = vectorMapC Cosh
139 tanh = vectorMapC Tanh
140 asinh = vectorMapC ASinh
141 acosh = vectorMapC ACosh
142 atanh = vectorMapC ATanh
143 exp = vectorMapC Exp
144 log = vectorMapC Log
145 sqrt = vectorMapC Sqrt
146 (**) = adaptScalar (vectorMapValC PowSV) (vectorZipC Pow) (flip (vectorMapValC PowVS))
147 pi = fromList [pi]
148
149---------------------------------------------------------------
150
151instance Floating (Matrix (Complex Double)) where
152 sin = liftMatrix sin
153 cos = liftMatrix cos
154 tan = liftMatrix tan
155 asin = liftMatrix asin
156 acos = liftMatrix acos
157 atan = liftMatrix atan
158 sinh = liftMatrix sinh
159 cosh = liftMatrix cosh
160 tanh = liftMatrix tanh
161 asinh = liftMatrix asinh
162 acosh = liftMatrix acosh
163 atanh = liftMatrix atanh
164 exp = liftMatrix exp
165 log = liftMatrix log
166 (**) = liftMatrix2 (**)
167 sqrt = liftMatrix sqrt
168 pi = (1><1) [pi]
169
170---------------------------------------------------------------
171
172
173class Mul a b c | a b -> c where
174 infixl 7 <>
175{- | 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.
176
177@v = 'fromList' [1,2,3] :: Vector Double
178cv = 'fromList' [1+'i',2]
179m = 'fromLists' [[1,2,3],
180 [4,5,7]] :: Matrix Double
181cm = 'fromLists' [[ 1, 2],
182 [3+'i',7*'i'],
183 [ 'i', 1]]
184\
185\> m \<\> v
18614. 35.
187\
188\> cv \<\> m
1899.+1.i 12.+2.i 17.+3.i
190\
191\> m \<\> cm
192 7.+5.i 5.+14.i
19319.+12.i 15.+35.i
194\
195\> v \<\> 'i'
1961.i 2.i 3.i
197\
198\> v \<\> v
19914.0
200\
201\> cv \<\> cv
2024.0 :+ 2.0@
203
204-}
205 (<>) :: a -> b -> c
206
207
208instance Mul Double Double Double where
209 (<>) = (*)
210
211instance Mul Double (Complex Double) (Complex Double) where
212 a <> b = (a:+0) * b
213
214instance Mul (Complex Double) Double (Complex Double) where
215 a <> b = a * (b:+0)
216
217instance Mul (Complex Double) (Complex Double) (Complex Double) where
218 (<>) = (*)
219
220--------------------------------- matrix matrix
221
222instance Mul (Matrix Double) (Matrix Double) (Matrix Double) where
223 (<>) = mXm
224
225instance Mul (Matrix (Complex Double)) (Matrix (Complex Double)) (Matrix (Complex Double)) where
226 (<>) = mXm
227
228instance Mul (Matrix (Complex Double)) (Matrix Double) (Matrix (Complex Double)) where
229 c <> r = c <> liftMatrix comp r
230
231instance Mul (Matrix Double) (Matrix (Complex Double)) (Matrix (Complex Double)) where
232 r <> c = liftMatrix comp r <> c
233
234--------------------------------- (Matrix Double) (Vector Double)
235
236instance Mul (Matrix Double) (Vector Double) (Vector Double) where
237 (<>) = mXv
238
239instance Mul (Matrix (Complex Double)) (Vector (Complex Double)) (Vector (Complex Double)) where
240 (<>) = mXv
241
242instance Mul (Matrix (Complex Double)) (Vector Double) (Vector (Complex Double)) where
243 m <> v = m <> comp v
244
245instance Mul (Matrix Double) (Vector (Complex Double)) (Vector (Complex Double)) where
246 m <> v = liftMatrix comp m <> v
247
248--------------------------------- (Vector Double) (Matrix Double)
249
250instance Mul (Vector Double) (Matrix Double) (Vector Double) where
251 (<>) = vXm
252
253instance Mul (Vector (Complex Double)) (Matrix (Complex Double)) (Vector (Complex Double)) where
254 (<>) = vXm
255
256instance Mul (Vector (Complex Double)) (Matrix Double) (Vector (Complex Double)) where
257 v <> m = v <> liftMatrix comp m
258
259instance Mul (Vector Double) (Matrix (Complex Double)) (Vector (Complex Double)) where
260 v <> m = comp v <> m
261
262--------------------------------- dot product
263
264instance Mul (Vector Double) (Vector Double) Double where
265 (<>) = dot
266
267instance Mul (Vector (Complex Double)) (Vector (Complex Double)) (Complex Double) where
268 (<>) = dot
269
270instance Mul (Vector Double) (Vector (Complex Double)) (Complex Double) where
271 a <> b = comp a <> b
272
273instance Mul (Vector (Complex Double)) (Vector Double) (Complex Double) where
274 (<>) = flip (<>)
275
276--------------------------------- scaling vectors
277
278instance Mul Double (Vector Double) (Vector Double) where
279 (<>) = scale
280
281instance Mul (Vector Double) Double (Vector Double) where
282 (<>) = flip (<>)
283
284instance Mul (Complex Double) (Vector (Complex Double)) (Vector (Complex Double)) where
285 (<>) = scale
286
287instance Mul (Vector (Complex Double)) (Complex Double) (Vector (Complex Double)) where
288 (<>) = flip (<>)
289
290instance Mul Double (Vector (Complex Double)) (Vector (Complex Double)) where
291 a <> v = (a:+0) <> v
292
293instance Mul (Vector (Complex Double)) Double (Vector (Complex Double)) where
294 (<>) = flip (<>)
295
296instance Mul (Complex Double) (Vector Double) (Vector (Complex Double)) where
297 a <> v = a <> comp v
298
299instance Mul (Vector Double) (Complex Double) (Vector (Complex Double)) where
300 (<>) = flip (<>)
301
302--------------------------------- scaling matrices
303
304instance Mul Double (Matrix Double) (Matrix Double) where
305 (<>) a = liftMatrix (a <>)
306
307instance Mul (Matrix Double) Double (Matrix Double) where
308 (<>) = flip (<>)
309
310instance Mul (Complex Double) (Matrix (Complex Double)) (Matrix (Complex Double)) where
311 (<>) a = liftMatrix (a <>)
312
313instance Mul (Matrix (Complex Double)) (Complex Double) (Matrix (Complex Double)) where
314 (<>) = flip (<>)
315
316instance Mul Double (Matrix (Complex Double)) (Matrix (Complex Double)) where
317 a <> m = (a:+0) <> m
318
319instance Mul (Matrix (Complex Double)) Double (Matrix (Complex Double)) where
320 (<>) = flip (<>)
321
322instance Mul (Complex Double) (Matrix Double) (Matrix (Complex Double)) where
323 a <> m = a <> liftMatrix comp m
324
325instance Mul (Matrix Double) (Complex Double) (Matrix (Complex Double)) where
326 (<>) = flip (<>)
327
328-----------------------------------------------------------------------------------
329
330size :: Vector a -> Int
331size = dim
332
333gmap f v = liftVector f v
334
335
336-- shows a Double with n digits after the decimal point
337shf :: (RealFloat a) => Int -> a -> String
338shf dec n | abs n < 1e-10 = "0."
339 | abs (n - (fromIntegral.round $ n)) < 1e-10 = show (round n) ++"."
340 | otherwise = showGFloat (Just dec) n ""
341-- shows a Complex Double as a pair, with n digits after the decimal point
342shfc n z@ (a:+b)
343 | magnitude z <1e-10 = "0."
344 | abs b < 1e-10 = shf n a
345 | abs a < 1e-10 = shf n b ++"i"
346 | b > 0 = shf n a ++"+"++shf n b ++"i"
347 | otherwise = shf n a ++shf n b ++"i"
348
349dsp :: String -> [[String]] -> String
350dsp sep as = unlines . map unwords' $ transpose mtp where
351 mt = transpose as
352 longs = map (maximum . map length) mt
353 mtp = zipWith (\a b -> map (pad a) b) longs mt
354 pad n str = replicate (n - length str) ' ' ++ str
355 unwords' = concat . intersperse sep
356
357format :: (Field t) => String -> (t -> String) -> Matrix t -> String
358format sep f m = dsp sep . map (map f) . toLists $ m
359
360disp m f = putStrLn $ "matrix ("++show (rows m) ++"x"++ show (cols m) ++")\n"++format " | " f m
361
362dispR :: Int -> Matrix Double -> IO ()
363dispR d m = disp m (shf d)
364
365dispC :: Int -> Matrix (Complex Double) -> IO ()
366dispC d m = disp m (shfc d)
367
368-- | creates a matrix from a table of numbers.
369readMatrix :: String -> Matrix Double
370readMatrix = fromLists . map (map read). map words . filter (not.null) . lines \ No newline at end of file
diff --git a/lib/GSL/Minimization.hs b/lib/GSL/Minimization.hs
index a59977e..aa89475 100644
--- a/lib/GSL/Minimization.hs
+++ b/lib/GSL/Minimization.hs
@@ -150,9 +150,11 @@ minimizeConjugateGradient istep minimpar tol maxit f df xi = unsafePerformIO $ d
150 df' = (fromList . df . toList) 150 df' = (fromList . df . toList)
151 fp <- mkVecfun (iv f') 151 fp <- mkVecfun (iv f')
152 dfp <- mkVecVecfun (aux_vTov df') 152 dfp <- mkVecVecfun (aux_vTov df')
153 print "entro"
153 rawpath <- createMIO maxit (n+2) 154 rawpath <- createMIO maxit (n+2)
154 (c_minimizeConjugateGradient fp dfp istep minimpar tol maxit // vec xiv) 155 (c_minimizeConjugateGradient fp dfp istep minimpar tol maxit // vec xiv)
155 "minimizeDerivV" [xiv] 156 "minimizeDerivV" [xiv]
157 print "salgo"
156 let it = round (rawpath @@> (maxit-1,0)) 158 let it = round (rawpath @@> (maxit-1,0))
157 path = takeRows it rawpath 159 path = takeRows it rawpath
158 sol = toList $ cdat $ dropColumns 2 $ dropRows (it-1) path 160 sol = toList $ cdat $ dropColumns 2 $ dropRows (it-1) path
@@ -186,12 +188,12 @@ foreign import ccall "wrapper"
186 188
187aux_vTov :: (Vector Double -> Vector Double) -> (Int -> Ptr Double -> Ptr Double -> IO()) 189aux_vTov :: (Vector Double -> Vector Double) -> (Int -> Ptr Double -> Ptr Double -> IO())
188aux_vTov f n p r = g where 190aux_vTov f n p r = g where
189 V {fptr = pr, ptr = p} = f x 191 V {fptr = pr, ptr = t} = f x
190 x = createV n copy "aux_vTov" [] 192 x = createV n copy "aux_vTov" []
191 copy n q = do 193 copy n q = do
192 copyArray q p n 194 copyArray q p n
193 return 0 195 return 0
194 g = withForeignPtr pr $ \_ -> copyArray r p n 196 g = withForeignPtr pr $ \_ -> copyArray r t n
195 197
196-------------------------------------------------------------------- 198--------------------------------------------------------------------
197 199