~ubuntu-branches/ubuntu/trusty/haskell-hmatrix/trusty

« back to all changes in this revision

Viewing changes to lib/Numeric/GSL/Minimization.hs

  • Committer: Package Import Robot
  • Author(s): Joachim Breitner
  • Date: 2013-06-04 21:54:51 UTC
  • Revision ID: package-import@ubuntu.com-20130604215451-czlj384n2drupnon
Tags: upstream-0.14.1.0
ImportĀ upstreamĀ versionĀ 0.14.1.0

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# LANGUAGE ForeignFunctionInterface #-}
 
2
-----------------------------------------------------------------------------
 
3
{- |
 
4
Module      :  Numeric.GSL.Minimization
 
5
Copyright   :  (c) Alberto Ruiz 2006-9
 
6
License     :  GPL-style
 
7
 
 
8
Maintainer  :  Alberto Ruiz (aruiz at um dot es)
 
9
Stability   :  provisional
 
10
Portability :  uses ffi
 
11
 
 
12
Minimization 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
 
 
16
The example in the GSL manual:
 
17
 
 
18
@
 
19
 
 
20
f [x,y] = 10*(x-1)^2 + 20*(y-2)^2 + 30
 
21
 
 
22
main = do
 
23
    let (s,p) = minimize NMSimplex2 1E-2 30 [1,1] f [5,7]
 
24
    print s
 
25
    print p
 
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
 ...
 
34
22.000   30.001  0.013  0.992  1.997
 
35
23.000   30.001  0.008  0.992  1.997
 
36
@
 
37
 
 
38
The path to the solution can be graphically shown by means of:
 
39
 
 
40
@'Graphics.Plot.mplot' $ drop 3 ('toColumns' p)@
 
41
 
 
42
Taken from the GSL manual:
 
43
 
 
44
The 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.
 
45
 
 
46
The 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).
 
47
 
 
48
The 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.
 
49
 
 
50
-}
 
51
 
 
52
-----------------------------------------------------------------------------
 
53
module Numeric.GSL.Minimization (
 
54
    minimize, minimizeV, MinimizeMethod(..),
 
55
    minimizeD, minimizeVD, MinimizeMethodD(..),
 
56
 
 
57
    minimizeNMSimplex,
 
58
    minimizeConjugateGradient,
 
59
    minimizeVectorBFGS2
 
60
) where
 
61
 
 
62
 
 
63
import Data.Packed.Internal
 
64
import Data.Packed.Matrix
 
65
import Numeric.GSL.Internal
 
66
 
 
67
import Foreign.Ptr(Ptr, FunPtr, freeHaskellFunPtr)
 
68
import Foreign.C.Types
 
69
import System.IO.Unsafe(unsafePerformIO)
 
70
 
 
71
------------------------------------------------------------------------
 
72
 
 
73
{-# DEPRECATED minimizeNMSimplex "use minimize NMSimplex2 eps maxit sizes f xi" #-}
 
74
minimizeNMSimplex 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" #-}
 
77
minimizeConjugateGradient 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" #-}
 
80
minimizeVectorBFGS2 step tol eps maxit f g xi = minimizeD VectorBFGS2 eps maxit step tol f g xi
 
81
 
 
82
-------------------------------------------------------------------------
 
83
 
 
84
data MinimizeMethod = NMSimplex
 
85
                    | NMSimplex2
 
86
                    deriving (Enum,Eq,Show,Bounded)
 
87
 
 
88
-- | Minimization without derivatives
 
89
minimize :: MinimizeMethod
 
90
         -> Double              -- ^ desired precision of the solution (size test)
 
91
         -> Int                 -- ^ maximum number of iterations allowed
 
92
         -> [Double]            -- ^ sizes of the initial search box
 
93
         -> ([Double] -> Double) -- ^ function to minimize
 
94
         -> [Double]            -- ^ starting point
 
95
         -> ([Double], Matrix Double) -- ^ solution vector and optimization path
 
96
 
 
97
-- | Minimization without derivatives (vector version)
 
98
minimizeV :: MinimizeMethod
 
99
         -> Double              -- ^ desired precision of the solution (size test)
 
100
         -> Int                 -- ^ maximum number of iterations allowed
 
101
         -> Vector Double       -- ^ sizes of the initial search box
 
102
         -> (Vector Double -> Double) -- ^ function to minimize
 
103
         -> Vector Double            -- ^ starting point
 
104
         -> (Vector Double, Matrix Double) -- ^ solution vector and optimization path
 
105
 
 
106
minimize method eps maxit sz f xi = v2l $ minimizeV method eps maxit (fromList sz) (f.toList) (fromList xi)
 
107
    where v2l (v,m) = (toList v, m)
 
108
 
 
109
ww2 w1 o1 w2 o2 f = w1 o1 $ \a1 -> w2 o2 $ \a2 -> f a1 a2
 
110
 
 
111
minimizeV method eps maxit szv f xiv = unsafePerformIO $ do
 
112
    let n   = dim xiv
 
113
    fp <- mkVecfun (iv f)
 
114
    rawpath <- ww2 vec xiv vec szv $ \xiv' szv' ->
 
115
                   createMIO maxit (n+3)
 
116
                         (c_minimize (fi (fromEnum method)) fp eps (fi maxit) // xiv' // szv')
 
117
                         "minimize"
 
118
    let it = round (rawpath @@> (maxit-1,0))
 
119
        path = takeRows it rawpath
 
120
        sol = cdat $ dropColumns 3 $ dropRows (it-1) path
 
121
    freeHaskellFunPtr fp
 
122
    return (sol, path)
 
123
 
 
124
 
 
125
foreign import ccall safe "gsl-aux.h minimize"
 
126
    c_minimize:: CInt -> FunPtr (CInt -> Ptr Double -> Double) -> Double -> CInt -> TVVM
 
127
 
 
128
----------------------------------------------------------------------------------
 
129
 
 
130
 
 
131
data MinimizeMethodD = ConjugateFR
 
132
                     | ConjugatePR
 
133
                     | VectorBFGS
 
134
                     | VectorBFGS2
 
135
                     | SteepestDescent
 
136
                     deriving (Enum,Eq,Show,Bounded)
 
137
 
 
138
-- | Minimization with derivatives.
 
139
minimizeD :: MinimizeMethodD
 
140
    -> Double                 -- ^ desired precision of the solution (gradient test)
 
141
    -> Int                    -- ^ maximum number of iterations allowed
 
142
    -> Double                 -- ^ size of the first trial step
 
143
    -> Double                 -- ^ tol (precise meaning depends on method)
 
144
    -> ([Double] -> Double)   -- ^ function to minimize
 
145
    -> ([Double] -> [Double]) -- ^ gradient
 
146
    -> [Double]               -- ^ starting point
 
147
    -> ([Double], Matrix Double) -- ^ solution vector and optimization path
 
148
 
 
149
-- | Minimization with derivatives (vector version)
 
150
minimizeVD :: MinimizeMethodD
 
151
    -> Double                 -- ^ desired precision of the solution (gradient test)
 
152
    -> Int                    -- ^ maximum number of iterations allowed
 
153
    -> Double                 -- ^ size of the first trial step
 
154
    -> Double                 -- ^ tol (precise meaning depends on method)
 
155
    -> (Vector Double -> Double)   -- ^ function to minimize
 
156
    -> (Vector Double -> Vector Double) -- ^ gradient
 
157
    -> Vector Double               -- ^ starting point
 
158
    -> (Vector Double, Matrix Double) -- ^ solution vector and optimization path
 
159
 
 
160
minimizeD method eps maxit istep tol f df xi = v2l $ minimizeVD
 
161
          method eps maxit istep tol (f.toList) (fromList.df.toList) (fromList xi)
 
162
    where v2l (v,m) = (toList v, m)
 
163
 
 
164
 
 
165
minimizeVD method eps maxit istep tol f df xiv = unsafePerformIO $ do
 
166
    let n = dim xiv
 
167
        f' = f
 
168
        df' = (checkdim1 n . df)
 
169
    fp <- mkVecfun (iv f')
 
170
    dfp <- mkVecVecfun (aux_vTov df')
 
171
    rawpath <- vec xiv $ \xiv' ->
 
172
                    createMIO maxit (n+2)
 
173
                         (c_minimizeD (fi (fromEnum method)) fp dfp istep tol eps (fi maxit) // xiv')
 
174
                         "minimizeD"
 
175
    let it = round (rawpath @@> (maxit-1,0))
 
176
        path = takeRows it rawpath
 
177
        sol = cdat $ dropColumns 2 $ dropRows (it-1) path
 
178
    freeHaskellFunPtr fp
 
179
    freeHaskellFunPtr dfp
 
180
    return (sol,path)
 
181
 
 
182
foreign import ccall safe "gsl-aux.h minimizeD"
 
183
    c_minimizeD :: CInt
 
184
                -> FunPtr (CInt -> Ptr Double -> Double)
 
185
                -> FunPtr TVV
 
186
                -> Double -> Double -> Double -> CInt
 
187
                -> TVM
 
188
 
 
189
---------------------------------------------------------------------
 
190
 
 
191
checkdim1 n v
 
192
    | dim v == n = v
 
193
    | otherwise = error $ "Error: "++ show n
 
194
                        ++ " components expected in the result of the gradient supplied to minimizeD"