summaryrefslogtreecommitdiff
path: root/lib/Numeric/GSL/Minimization.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Numeric/GSL/Minimization.hs')
-rw-r--r--lib/Numeric/GSL/Minimization.hs227
1 files changed, 0 insertions, 227 deletions
diff --git a/lib/Numeric/GSL/Minimization.hs b/lib/Numeric/GSL/Minimization.hs
deleted file mode 100644
index 1879dab..0000000
--- a/lib/Numeric/GSL/Minimization.hs
+++ /dev/null
@@ -1,227 +0,0 @@
1{-# LANGUAGE ForeignFunctionInterface #-}
2-----------------------------------------------------------------------------
3{- |
4Module : Numeric.GSL.Minimization
5Copyright : (c) Alberto Ruiz 2006-9
6License : GPL-style
7
8Maintainer : Alberto Ruiz (aruiz at um dot es)
9Stability : provisional
10Portability : uses ffi
11
12Minimization of a multidimensional function using some of the algorithms described in:
13
14<http://www.gnu.org/software/gsl/manual/html_node/Multidimensional-Minimization.html>
15
16The example in the GSL manual:
17
18@
19f [x,y] = 10*(x-1)^2 + 20*(y-2)^2 + 30
20
21main = do
22 let (s,p) = minimize NMSimplex2 1E-2 30 [1,1] f [5,7]
23 print s
24 print p
25@
26
27>>> main
28[0.9920430849306288,1.9969168063253182]
29 0.000 512.500 1.130 6.500 5.000
30 1.000 290.625 1.409 5.250 4.000
31 2.000 290.625 1.409 5.250 4.000
32 3.000 252.500 1.409 5.500 1.000
33 ...
3422.000 30.001 0.013 0.992 1.997
3523.000 30.001 0.008 0.992 1.997
36
37The path to the solution can be graphically shown by means of:
38
39@'Graphics.Plot.mplot' $ drop 3 ('toColumns' p)@
40
41Taken from the GSL manual:
42
43The vector Broyden-Fletcher-Goldfarb-Shanno (BFGS) algorithm is a quasi-Newton method which builds up an approximation to the second derivatives of the function f using the difference between successive gradient vectors. By combining the first and second derivatives the algorithm is able to take Newton-type steps towards the function minimum, assuming quadratic behavior in that region.
44
45The bfgs2 version of this minimizer is the most efficient version available, and is a faithful implementation of the line minimization scheme described in Fletcher's Practical Methods of Optimization, Algorithms 2.6.2 and 2.6.4. It supercedes the original bfgs routine and requires substantially fewer function and gradient evaluations. The user-supplied tolerance tol corresponds to the parameter \sigma used by Fletcher. A value of 0.1 is recommended for typical use (larger values correspond to less accurate line searches).
46
47The nmsimplex2 version is a new O(N) implementation of the earlier O(N^2) nmsimplex minimiser. It calculates the size of simplex as the rms distance of each vertex from the center rather than the mean distance, which has the advantage of allowing a linear update.
48
49-}
50
51-----------------------------------------------------------------------------
52module Numeric.GSL.Minimization (
53 minimize, minimizeV, MinimizeMethod(..),
54 minimizeD, minimizeVD, MinimizeMethodD(..),
55 uniMinimize, UniMinimizeMethod(..),
56
57 minimizeNMSimplex,
58 minimizeConjugateGradient,
59 minimizeVectorBFGS2
60) where
61
62
63import Data.Packed.Internal
64import Data.Packed.Matrix
65import Numeric.GSL.Internal
66
67import Foreign.Ptr(Ptr, FunPtr, freeHaskellFunPtr)
68import Foreign.C.Types
69import System.IO.Unsafe(unsafePerformIO)
70
71------------------------------------------------------------------------
72
73{-# DEPRECATED minimizeNMSimplex "use minimize NMSimplex2 eps maxit sizes f xi" #-}
74minimizeNMSimplex f xi szs eps maxit = minimize NMSimplex eps maxit szs f xi
75
76{-# DEPRECATED minimizeConjugateGradient "use minimizeD ConjugateFR eps maxit step tol f g xi" #-}
77minimizeConjugateGradient step tol eps maxit f g xi = minimizeD ConjugateFR eps maxit step tol f g xi
78
79{-# DEPRECATED minimizeVectorBFGS2 "use minimizeD VectorBFGS2 eps maxit step tol f g xi" #-}
80minimizeVectorBFGS2 step tol eps maxit f g xi = minimizeD VectorBFGS2 eps maxit step tol f g xi
81
82-------------------------------------------------------------------------
83
84data UniMinimizeMethod = GoldenSection
85 | BrentMini
86 | QuadGolden
87 deriving (Enum, Eq, Show, Bounded)
88
89-- | Onedimensional minimization.
90
91uniMinimize :: UniMinimizeMethod -- ^ The method used.
92 -> Double -- ^ desired precision of the solution
93 -> Int -- ^ maximum number of iterations allowed
94 -> (Double -> Double) -- ^ function to minimize
95 -> Double -- ^ guess for the location of the minimum
96 -> Double -- ^ lower bound of search interval
97 -> Double -- ^ upper bound of search interval
98 -> (Double, Matrix Double) -- ^ solution and optimization path
99
100uniMinimize method epsrel maxit fun xmin xl xu = uniMinimizeGen (fi (fromEnum method)) fun xmin xl xu epsrel maxit
101
102uniMinimizeGen m f xmin xl xu epsrel maxit = unsafePerformIO $ do
103 fp <- mkDoublefun f
104 rawpath <- createMIO maxit 4
105 (c_uniMinize m fp epsrel (fi maxit) xmin xl xu)
106 "uniMinimize"
107 let it = round (rawpath @@> (maxit-1,0))
108 path = takeRows it rawpath
109 [sol] = toLists $ dropRows (it-1) path
110 freeHaskellFunPtr fp
111 return (sol !! 1, path)
112
113
114foreign import ccall safe "uniMinimize"
115 c_uniMinize:: CInt -> FunPtr (Double -> Double) -> Double -> CInt -> Double -> Double -> Double -> TM
116
117data MinimizeMethod = NMSimplex
118 | NMSimplex2
119 deriving (Enum,Eq,Show,Bounded)
120
121-- | Minimization without derivatives
122minimize :: MinimizeMethod
123 -> Double -- ^ desired precision of the solution (size test)
124 -> Int -- ^ maximum number of iterations allowed
125 -> [Double] -- ^ sizes of the initial search box
126 -> ([Double] -> Double) -- ^ function to minimize
127 -> [Double] -- ^ starting point
128 -> ([Double], Matrix Double) -- ^ solution vector and optimization path
129
130-- | Minimization without derivatives (vector version)
131minimizeV :: MinimizeMethod
132 -> Double -- ^ desired precision of the solution (size test)
133 -> Int -- ^ maximum number of iterations allowed
134 -> Vector Double -- ^ sizes of the initial search box
135 -> (Vector Double -> Double) -- ^ function to minimize
136 -> Vector Double -- ^ starting point
137 -> (Vector Double, Matrix Double) -- ^ solution vector and optimization path
138
139minimize method eps maxit sz f xi = v2l $ minimizeV method eps maxit (fromList sz) (f.toList) (fromList xi)
140 where v2l (v,m) = (toList v, m)
141
142ww2 w1 o1 w2 o2 f = w1 o1 $ \a1 -> w2 o2 $ \a2 -> f a1 a2
143
144minimizeV method eps maxit szv f xiv = unsafePerformIO $ do
145 let n = dim xiv
146 fp <- mkVecfun (iv f)
147 rawpath <- ww2 vec xiv vec szv $ \xiv' szv' ->
148 createMIO maxit (n+3)
149 (c_minimize (fi (fromEnum method)) fp eps (fi maxit) // xiv' // szv')
150 "minimize"
151 let it = round (rawpath @@> (maxit-1,0))
152 path = takeRows it rawpath
153 sol = cdat $ dropColumns 3 $ dropRows (it-1) path
154 freeHaskellFunPtr fp
155 return (sol, path)
156
157
158foreign import ccall safe "gsl-aux.h minimize"
159 c_minimize:: CInt -> FunPtr (CInt -> Ptr Double -> Double) -> Double -> CInt -> TVVM
160
161----------------------------------------------------------------------------------
162
163
164data MinimizeMethodD = ConjugateFR
165 | ConjugatePR
166 | VectorBFGS
167 | VectorBFGS2
168 | SteepestDescent
169 deriving (Enum,Eq,Show,Bounded)
170
171-- | Minimization with derivatives.
172minimizeD :: MinimizeMethodD
173 -> Double -- ^ desired precision of the solution (gradient test)
174 -> Int -- ^ maximum number of iterations allowed
175 -> Double -- ^ size of the first trial step
176 -> Double -- ^ tol (precise meaning depends on method)
177 -> ([Double] -> Double) -- ^ function to minimize
178 -> ([Double] -> [Double]) -- ^ gradient
179 -> [Double] -- ^ starting point
180 -> ([Double], Matrix Double) -- ^ solution vector and optimization path
181
182-- | Minimization with derivatives (vector version)
183minimizeVD :: MinimizeMethodD
184 -> Double -- ^ desired precision of the solution (gradient test)
185 -> Int -- ^ maximum number of iterations allowed
186 -> Double -- ^ size of the first trial step
187 -> Double -- ^ tol (precise meaning depends on method)
188 -> (Vector Double -> Double) -- ^ function to minimize
189 -> (Vector Double -> Vector Double) -- ^ gradient
190 -> Vector Double -- ^ starting point
191 -> (Vector Double, Matrix Double) -- ^ solution vector and optimization path
192
193minimizeD method eps maxit istep tol f df xi = v2l $ minimizeVD
194 method eps maxit istep tol (f.toList) (fromList.df.toList) (fromList xi)
195 where v2l (v,m) = (toList v, m)
196
197
198minimizeVD method eps maxit istep tol f df xiv = unsafePerformIO $ do
199 let n = dim xiv
200 f' = f
201 df' = (checkdim1 n . df)
202 fp <- mkVecfun (iv f')
203 dfp <- mkVecVecfun (aux_vTov df')
204 rawpath <- vec xiv $ \xiv' ->
205 createMIO maxit (n+2)
206 (c_minimizeD (fi (fromEnum method)) fp dfp istep tol eps (fi maxit) // xiv')
207 "minimizeD"
208 let it = round (rawpath @@> (maxit-1,0))
209 path = takeRows it rawpath
210 sol = cdat $ dropColumns 2 $ dropRows (it-1) path
211 freeHaskellFunPtr fp
212 freeHaskellFunPtr dfp
213 return (sol,path)
214
215foreign import ccall safe "gsl-aux.h minimizeD"
216 c_minimizeD :: CInt
217 -> FunPtr (CInt -> Ptr Double -> Double)
218 -> FunPtr TVV
219 -> Double -> Double -> Double -> CInt
220 -> TVM
221
222---------------------------------------------------------------------
223
224checkdim1 n v
225 | dim v == n = v
226 | otherwise = error $ "Error: "++ show n
227 ++ " components expected in the result of the gradient supplied to minimizeD"