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

This time-controlled driver shows that it is possible to terminate a run by elapsed CPU time, and yet be able to print all desired information. This driver also illustrates the use of two stopping criteria that may be used in conjunction with a limit on execution time. The sample problem used here is the same as in driver1 and driver2 (the extended Rosenbrock function with bounds on the variables). (Fortran-90 version)

1 !> \file driver3.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 ! DRIVER 3 in Fortran 90
9 ! --------------------------------------------------------------
10 ! TIME-CONTROLLED DRIVER FOR L-BFGS-B
11 ! --------------------------------------------------------------
12 !
13 ! L-BFGS-B is a code for solving large nonlinear optimization
14 ! problems with simple bounds on the variables.
15 !
16 ! The code can also be used for unconstrained problems and is
17 ! as efficient for these problems as the earlier limited memory
18 ! code L-BFGS.
19 !
20 ! This driver shows how to terminate a run after some prescribed
21 ! CPU time has elapsed, and how to print the desired information
22 ! before exiting.
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 
49  program driver
50 
51 ! This time-controlled driver shows that it is possible to terminate
52 ! a run by elapsed CPU time, and yet be able to print all desired
53 ! information. This driver also illustrates the use of two
54 ! stopping criteria that may be used in conjunction with a limit
55 ! on execution time. The sample problem used here is the same as in
56 ! driver1 and driver2 (the extended Rosenbrock function with bounds
57 ! on the variables).
58 
59  implicit none
60 
61 ! We specify a limit on the CPU time (tlimit = 10 seconds)
62 !
63 ! We suppress the default output (iprint = -1). The user could
64 ! also elect to use the default output by choosing iprint >= 0.)
65 ! We suppress the code-supplied stopping tests because we will
66 ! provide our own termination conditions
67 ! We specify the dimension n of the sample problem and the number
68 ! m of limited memory corrections stored.
69 
70  integer, parameter :: n = 1000, m = 10, iprint = -1
71  integer, parameter :: dp = kind(1.0d0)
72  real(dp), parameter :: factr = 0.0d0, pgtol = 0.0d0, &
73  tlimit = 10.0d0
74 !
75  character(len=60) :: task, csave
76  logical :: lsave(4)
77  integer :: isave(44)
78  real(dp) :: f
79  real(dp) :: dsave(29)
80  integer, allocatable :: nbd(:), iwa(:)
81  real(dp), allocatable :: x(:), l(:), u(:), g(:), wa(:)
82 !
83  real(dp) :: t1, t2, time1, time2
84  integer :: i, j
85 
86  allocate ( nbd(n), x(n), l(n), u(n), g(n) )
87  allocate ( iwa(3*n) )
88  allocate ( wa(2*m*n + 5*n + 11*m*m + 8*m) )
89 
90 ! This time-controlled driver shows that it is possible to terminate
91 ! a run by elapsed CPU time, and yet be able to print all desired
92 ! information. This driver also illustrates the use of two
93 ! stopping criteria that may be used in conjunction with a limit
94 ! on execution time. The sample problem used here is the same as in
95 ! driver1 and driver2 (the extended Rosenbrock function with bounds
96 ! on the variables).
97 
98 ! We now specify nbd which defines the bounds on the variables:
99 ! l specifies the lower bounds,
100 ! u specifies the upper bounds.
101 
102 ! First set bounds on the odd-numbered variables.
103 
104  do 10 i=1, n,2
105  nbd(i)=2
106  l(i)=1.0d0
107  u(i)=1.0d2
108  10 continue
109 
110 ! Next set bounds on the even-numbered variables.
111 
112  do 12 i=2, n,2
113  nbd(i)=2
114  l(i)=-1.0d2
115  u(i)=1.0d2
116  12 continue
117 
118 ! We now define the starting point.
119 
120  do 14 i=1, n
121  x(i)=3.0d0
122  14 continue
123 
124 ! We now write the heading of the output.
125 
126  write (6,16)
127  16 format(/,5x, 'Solving sample problem.',&
128  /,5x, ' (f = 0.0 at the optimal solution.)',/)
129 
130 ! We start the iteration by initializing task.
131 
132  task = 'START'
133 
134 ! ------- the beginning of the loop ----------
135 
136 ! We begin counting the CPU time.
137 
138  call timer(time1)
139 
140  do while( task(1:2).eq.'FG'.or.task.eq.'NEW_X'.or. &
141  task.eq.'START')
142 
143 ! This is the call to the L-BFGS-B code.
144 
145  call setulb(n,m,x,l,u,nbd,f,g,factr,pgtol,wa,iwa, &
146  task,iprint, csave,lsave,isave,dsave)
147 
148  if (task(1:2) .eq. 'FG') then
149 
150 ! the minimization routine has returned to request the
151 ! function f and gradient g values at the current x.
152 ! Before evaluating f and g we check the CPU time spent.
153 
154  call timer(time2)
155  if (time2-time1 .gt. tlimit) then
156  task='STOP: CPU EXCEEDING THE TIME LIMIT.'
157 
158 ! Note: Assigning task(1:4)='STOP' will terminate the run;
159 ! setting task(7:9)='CPU' will restore the information at
160 ! the latest iterate generated by the code so that it can
161 ! be correctly printed by the driver.
162 
163 ! In this driver we have chosen to disable the
164 ! printing options of the code (we set iprint=-1);
165 ! instead we are using customized output: we print the
166 ! latest value of x, the corresponding function value f and
167 ! the norm of the projected gradient |proj g|.
168 
169 ! We print out the information contained in task.
170 
171  write (6,*) task
172 
173 ! We print the latest iterate contained in wa(j+1:j+n), where
174 
175  j = 3*n+2*m*n+11*m**2
176  write (6,*) 'Latest iterate X ='
177  write (6,'((1x,1p, 6(1x,d11.4)))') (wa(i),i = j+1,j+n)
178 
179 ! We print the function value f and the norm of the projected
180 ! gradient |proj g| at the last iterate; they are stored in
181 ! dsave(2) and dsave(13) respectively.
182 
183  write (6,'(a,1p,d12.5,4x,a,1p,d12.5)') &
184  'At latest iterate f =',dsave(2),'|proj g| =',dsave(13)
185  else
186 
187 ! The time limit has not been reached and we compute
188 ! the function value f for the sample problem.
189 
190  f=.25d0*(x(1)-1.d0)**2
191  do 20 i=2, n
192  f=f+(x(i)-x(i-1)**2)**2
193  20 continue
194  f=4.d0*f
195 
196 ! Compute gradient g for the sample problem.
197 
198  t1 = x(2) - x(1)**2
199  g(1) = 2.d0*(x(1)-1.d0)-1.6d1*x(1)*t1
200  do 22 i=2,n-1
201  t2=t1
202  t1=x(i+1)-x(i)**2
203  g(i)=8.d0*t2-1.6d1*x(i)*t1
204  22 continue
205  g(n)=8.d0*t1
206  endif
207 
208 ! go back to the minimization routine.
209  else
210 
211  if (task(1:5) .eq. 'NEW_X') then
212 
213 ! the minimization routine has returned with a new iterate.
214 ! The time limit has not been reached, and we test whether
215 ! the following two stopping tests are satisfied:
216 
217 ! 1) Terminate if the total number of f and g evaluations
218 ! exceeds 900.
219 
220  if (isave(34) .ge. 900) &
221  task='STOP: TOTAL NO. of f AND g EVALUATIONS EXCEEDS LIMIT'
222 
223 ! 2) Terminate if |proj g|/(1+|f|) < 1.0d-10.
224 
225  if (dsave(13) .le. 1.d-10*(1.0d0 + abs(f))) &
226  task='STOP: THE PROJECTED GRADIENT IS SUFFICIENTLY SMALL'
227 
228 ! We wish to print the following information at each iteration:
229 ! 1) the current iteration number, isave(30),
230 ! 2) the total number of f and g evaluations, isave(34),
231 ! 3) the value of the objective function f,
232 ! 4) the norm of the projected gradient, dsve(13)
233 !
234 ! See the comments at the end of driver1 for a description
235 ! of the variables isave and dsave.
236 
237  write (6,'(2(a,i5,4x),a,1p,d12.5,4x,a,1p,d12.5)') 'Iterate' &
238  ,isave(30),'nfg =',isave(34),'f =',f,'|proj g| =',dsave(13)
239 
240 ! If the run is to be terminated, we print also the information
241 ! contained in task as well as the final value of x.
242 
243  if (task(1:4) .eq. 'STOP') then
244  write (6,*) task
245  write (6,*) 'Final X='
246  write (6,'((1x,1p, 6(1x,d11.4)))') (x(i),i = 1,n)
247  endif
248 
249  endif
250  end if
251  end do
252 
253 ! If task is neither FG nor NEW_X we terminate execution.
254 
255  end program driver
256 
257 !======================= The end of driver3 ============================
258 
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
subroutine timer(ttime)
This routine computes cpu time in double precision.
Definition: timer.f:11