L-BFGS-B  3.0
Large-scale Bound-constrained Optimization
driver2.f90

This driver shows how to replace the default stopping test by other termination criteria. It also illustrates how to print the values of several parameters during the course of the iteration. The sample problem used here is the same as in DRIVER1 (the extended Rosenbrock function with bounds on the variables). (Fortran-90 version)

1 !> \file driver2.f90
2 
3 !
4 ! L-BFGS-B is released under the “New BSD License” (aka “Modified BSD License”
5 ! or “3-clause license”)
6 ! Please read attached file License.txt
7 !
8 !
9 ! DRIVER 2 in Fortran 90
10 ! --------------------------------------------------------------
11 ! CUSTOMIZED DRIVER FOR L-BFGS-B
12 ! --------------------------------------------------------------
13 !
14 ! L-BFGS-B is a code for solving large nonlinear optimization
15 ! problems with simple bounds on the variables.
16 !
17 ! The code can also be used for unconstrained problems and is
18 ! as efficient for these problems as the earlier limited memory
19 ! code L-BFGS.
20 !
21 ! This driver illustrates how to control the termination of the
22 ! run and how to design customized output.
23 !
24 ! References:
25 !
26 ! [1] R. H. Byrd, P. Lu, J. Nocedal and C. Zhu, ``A limited
27 ! memory algorithm for bound constrained optimization'',
28 ! SIAM J. Scientific Computing 16 (1995), no. 5, pp. 1190--1208.
29 !
30 ! [2] C. Zhu, R.H. Byrd, P. Lu, J. Nocedal, ``L-BFGS-B: FORTRAN
31 ! Subroutines for Large Scale Bound Constrained Optimization''
32 ! Tech. Report, NAM-11, EECS Department, Northwestern University,
33 ! 1994.
34 !
35 !
36 ! (Postscript files of these papers are available via anonymous
37 ! ftp to eecs.nwu.edu in the directory pub/lbfgs/lbfgs_bcm.)
38 !
39 ! * * *
40 !
41 ! February 2011 (latest revision)
42 ! Optimization Center at Northwestern University
43 ! Instituto Tecnologico Autonomo de Mexico
44 !
45 ! Jorge Nocedal and Jose Luis Morales
46 !
47 ! **************
48  program driver
49 
50 ! This driver shows how to replace the default stopping test
51 ! by other termination criteria. It also illustrates how to
52 ! print the values of several parameters during the course of
53 ! the iteration. The sample problem used here is the same as in
54 ! DRIVER1 (the extended Rosenbrock function with bounds on the
55 ! variables).
56 
57  implicit none
58 
59 ! Declare variables and parameters needed by the code.
60 !
61 ! Note that we suppress the default output (iprint = -1)
62 ! We suppress both code-supplied stopping tests because the
63 ! user is providing his/her own stopping criteria.
64 
65  integer, parameter :: n = 25, m = 5, iprint = -1
66  integer, parameter :: dp = kind(1.0d0)
67  real(dp), parameter :: factr = 0.0d0, pgtol = 0.0d0
68 
69  character(len=60) :: task, csave
70  logical :: lsave(4)
71  integer :: isave(44)
72  real(dp) :: f
73  real(dp) :: dsave(29)
74  integer, allocatable :: nbd(:), iwa(:)
75  real(dp), allocatable :: x(:), l(:), u(:), g(:), wa(:)
76 !
77  real(dp) :: t1, t2
78  integer :: i
79 
80  allocate ( nbd(n), x(n), l(n), u(n), g(n) )
81  allocate ( iwa(3*n) )
82  allocate ( wa(2*m*n + 5*n + 11*m*m + 8*m) )
83 !
84 ! This driver shows how to replace the default stopping test
85 ! by other termination criteria. It also illustrates how to
86 ! print the values of several parameters during the course of
87 ! the iteration. The sample problem used here is the same as in
88 ! DRIVER1 (the extended Rosenbrock function with bounds on the
89 ! variables).
90 ! We now specify nbd which defines the bounds on the variables:
91 ! l specifies the lower bounds,
92 ! u specifies the upper bounds.
93 
94 ! First set bounds on the odd numbered variables.
95 
96  do 10 i=1, n,2
97  nbd(i)=2
98  l(i)=1.0d0
99  u(i)=1.0d2
100  10 continue
101 
102 ! Next set bounds on the even numbered variables.
103 
104  do 12 i=2, n,2
105  nbd(i)=2
106  l(i)=-1.0d2
107  u(i)=1.0d2
108  12 continue
109 
110 ! We now define the starting point.
111 
112  do 14 i=1, n
113  x(i)=3.0d0
114  14 continue
115 
116 ! We now write the heading of the output.
117 
118  write (6,16)
119  16 format(/,5x, 'Solving sample problem.', &
120  /,5x, ' (f = 0.0 at the optimal solution.)',/)
121 
122 
123 ! We start the iteration by initializing task.
124 !
125  task = 'START'
126 
127 ! ------- the beginning of the loop ----------
128 
129  do while( task(1:2).eq.'FG'.or.task.eq.'NEW_X'.or. &
130  task.eq.'START')
131 
132 ! This is the call to the L-BFGS-B code.
133 
134  call setulb(n,m,x,l,u,nbd,f,g,factr,pgtol,wa,iwa,task,iprint, &
135  csave,lsave,isave,dsave)
136 
137  if (task(1:2) .eq. 'FG') then
138 
139 ! the minimization routine has returned to request the
140 ! function f and gradient g values at the current x.
141 
142 ! Compute function value f for the sample problem.
143 
144  f =.25d0*(x(1) - 1.d0)**2
145  do 20 i=2,n
146  f = f + (x(i) - x(i-1)**2)**2
147  20 continue
148  f = 4.d0*f
149 
150 ! Compute gradient g for the sample problem.
151 
152  t1 = x(2) - x(1)**2
153  g(1) = 2.d0*(x(1) - 1.d0) - 1.6d1*x(1)*t1
154  do 22 i= 2,n-1
155  t2 = t1
156  t1 = x(i+1) - x(i)**2
157  g(i) = 8.d0*t2 - 1.6d1*x(i)*t1
158  22 continue
159  g(n)=8.d0*t1
160 !
161  else
162 !
163  if (task(1:5) .eq. 'NEW_X') then
164 !
165 ! the minimization routine has returned with a new iterate.
166 ! At this point have the opportunity of stopping the iteration
167 ! or observing the values of certain parameters
168 !
169 ! First are two examples of stopping tests.
170 
171 ! Note: task(1:4) must be assigned the value 'STOP' to terminate
172 ! the iteration and ensure that the final results are
173 ! printed in the default format. The rest of the character
174 ! string TASK may be used to store other information.
175 
176 ! 1) Terminate if the total number of f and g evaluations
177 ! exceeds 99.
178 
179  if (isave(34) .ge. 99) &
180  task='STOP: TOTAL NO. of f AND g EVALUATIONS EXCEEDS LIMIT'
181 
182 ! 2) Terminate if |proj g|/(1+|f|) < 1.0d-10, where
183 ! "proj g" denoted the projected gradient
184 
185  if (dsave(13) .le. 1.d-10*(1.0d0 + abs(f))) &
186  task='STOP: THE PROJECTED GRADIENT IS SUFFICIENTLY SMALL'
187 
188 ! We now wish to print the following information at each
189 ! iteration:
190 !
191 ! 1) the current iteration number, isave(30),
192 ! 2) the total number of f and g evaluations, isave(34),
193 ! 3) the value of the objective function f,
194 ! 4) the norm of the projected gradient, dsve(13)
195 !
196 ! See the comments at the end of driver1 for a description
197 ! of the variables isave and dsave.
198 
199  write (6,'(2(a,i5,4x),a,1p,d12.5,4x,a,1p,d12.5)') 'Iterate' &
200  , isave(30),'nfg =',isave(34),'f =',f,'|proj g| =',dsave(13)
201 
202 ! If the run is to be terminated, we print also the information
203 ! contained in task as well as the final value of x.
204 
205  if (task(1:4) .eq. 'STOP') then
206  write (6,*) task
207  write (6,*) 'Final X='
208  write (6,'((1x,1p, 6(1x,d11.4)))') (x(i),i = 1,n)
209  end if
210 
211  end if
212  end if
213 
214  end do
215 ! ---------- the end of the loop -------------
216 
217 ! If task is neither FG nor NEW_X we terminate execution.
218 
219  end program driver
220 
221 !======================= The end of driver2 ============================
222 
subroutine setulb(n, m, x, l, u, nbd, f, g, factr, pgtol, wa, iwa, task, iprint, csave, lsave, isave, dsave)
This subroutine partitions the working arrays wa and iwa, and then uses the limited memory BFGS metho...
Definition: setulb.f:190