setulb Subroutine

public subroutine setulb(n, m, x, l, u, Nbd, f, g, Factr, Pgtol, Wa, Iwa, Task, Iprint, Csave, Lsave, Isave, Dsave, iteration_file)

The main routine.

This subroutine partitions the working arrays wa and iwa, and then uses the limited memory BFGS method to solve the bound constrained optimization problem by calling mainlb. (The direct method will be used in the subspace minimization.)

References

  1. R. H. Byrd, P. Lu, J. Nocedal and C. Zhu, "A limited memory algorithm for bound constrained optimization", SIAM J. Scientific Computing 16 (1995), no. 5, pp. 1190--1208.
  2. C. Zhu, R.H. Byrd, P. Lu, J. Nocedal, "L-BFGS-B: a limited memory FORTRAN code for solving bound constrained optimization problems", Tech. Report, NAM-11, EECS Department, Northwestern University, 1994.

History

  • NEOS, November 1994. (Latest revision June 1996.) Optimization Technology Center. Argonne National Laboratory and Northwestern University. Written by Ciyou Zhu in collaboration with R.H. Byrd, P. Lu-Chen and J. Nocedal.

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: n

the dimension of the problem (the number of variables).

integer, intent(in) :: m

the maximum number of variable metric corrections used to define the limited memory matrix. Values of m < 3 are not recommended, and large values of m can result in excessive computing time. The range 3 <= m <= 20 is recommended.

real(kind=wp), intent(inout) :: x(n)

On initial entry it must be set by the user to the values of the initial estimate of the solution vector. Upon successful exit, it contains the values of the variables at the best point found (usually an approximate solution).

real(kind=wp), intent(in) :: l(n)

the lower bound on x. If the i-th variable has no lower bound, l(i) need not be defined.

real(kind=wp), intent(in) :: u(n)

the upper bound on x. If the i-th variable has no upper bound, u(i) need not be defined.

integer, intent(in) :: Nbd(n)

nbd represents the type of bounds imposed on the variables, and must be specified as follows:

  • nbd(i)=0 if x(i) is unbounded
  • nbd(i)=1 if x(i) has only a lower bound
  • nbd(i)=2 if x(i) has both lower and upper bounds
  • nbd(i)=3 if x(i) has only an upper bound
real(kind=wp), intent(inout) :: f

On first entry f is unspecified. On final exit f is the value of the function at x. If the setulb returns with task(1:2)= 'FG', then f must be set by the user to contain the value of the function at the point x.

real(kind=wp), intent(inout) :: g(n)

On first entry g is unspecified. On final exit g is the value of the gradient at x. If the setulb returns with task(1:2)= 'FG', then g must be set by the user to contain the components of the gradient at the point x.

real(kind=wp), intent(in) :: Factr

A tolerance in the termination test for the algorithm. The iteration will stop when:

(f^k - f^{k+1})/max{|f^k|,|f^{k+1}|,1} <= factr*epsmch

where epsmch is the machine precision. Typical values for factr on a computer with 15 digits of accuracy in real(wp) are:

  • factr=1.0e+12 for low accuracy
  • factr=1.0e+7 for moderate accuracy
  • factr=1.0e+1 for extremely high accuracy

The user can suppress this termination test by setting factr=0.

real(kind=wp), intent(in) :: Pgtol

The iteration will stop when:

max{|proj g_i | i = 1, ..., n} <= pgtol

where pg_i is the ith component of the projected gradient. The user can suppress this termination test by setting pgtol=0.

real(kind=wp) :: Wa(2*m*n+5*n+11*m*m+8*m)

working array of length (2mmax + 5)nmax + 11mmax^2 + 8mmax. This array must not be altered by the user.

integer :: Iwa(3*n)

an integer working array of length 3nmax. This array must not be altered by the user.

character(len=60), intent(inout) :: Task

Indicates the current job when entering and quitting this subroutine:

  • On first entry, it must be set to 'START'.
  • On a return with task(1:2)='FG', the user must evaluate the function f and gradient g at the returned value of x.
  • On a return with task(1:5)='NEW_X', an iteration of the algorithm has concluded, and f and g contain f(x) and g(x) respectively. The user can decide whether to continue or stop the iteration.
  • When task(1:4)='CONV', the termination test in L-BFGS-B has been satisfied;
  • When task(1:4)='ABNO', the routine has terminated abnormally without being able to satisfy the termination conditions, x contains the best approximation found, f and g contain f(x) and g(x) respectively;
  • When task(1:5)='ERROR', the routine has detected an error in the input parameters;

On exit with task = 'CONV', 'ABNO' or 'ERROR', the variable task contains additional information that the user can print.

This array should not be altered unless the user wants to stop the run for some reason. See driver2 or driver3 for a detailed explanation on how to stop the run by assigning task(1:4)='STOP' in the driver.

integer, intent(in) :: Iprint

Controls the frequency and type of output generated:

  • iprint<0 no output is generated
  • iprint=0 print only one line at the last iteration
  • 0<iprint<99 print also f and |proj g| every iprint iterations
  • iprint=99 print details of every iteration except n-vectors
  • iprint=100 print also the changes of active set and final x
  • iprint>100 print details of every iteration including x and g

When iprint > 0, the file iterate.dat will be created to summarize the iteration.

character(len=60) :: Csave

working string

logical :: Lsave(4)

A logical working array of dimension 4. On exit with task = 'NEW_X', the following information is available:

  • If lsave(1) = .true. then the initial x did not satisfy the bounds and x has been replaced by its projection in the feasible set
  • If lsave(2) = .true. then the problem is constrained
  • If lsave(3) = .true. then each variable has upper and lower bounds
integer :: Isave(44)

An integer working array of dimension 44. On exit with 'task' = NEW_X, the following information is available:

  • isave(22) = the total number of intervals explored in the search of Cauchy points;
  • isave(26) = the total number of skipped BFGS updates before the current iteration;
  • isave(30) = the number of current iteration;
  • isave(31) = the total number of BFGS updates prior the current iteration;
  • isave(33) = the number of intervals explored in the search of Cauchy point in the current iteration;
  • isave(34) = the total number of function and gradient evaluations;
  • isave(36) = the number of function value or gradient evaluations in the current iteration;
  • if isave(37) = 0 then the subspace argmin is within the box;
  • if isave(37) = 1 then the subspace argmin is beyond the box;
  • isave(38) = the number of free variables in the current iteration;
  • isave(39) = the number of active constraints in the current iteration;
  • n + 1 - isave(40) = the number of variables leaving the set of active constraints in the current iteration;
  • isave(41) = the number of variables entering the set of active constraints in the current iteration.
real(kind=wp) :: Dsave(29)

A real(wp) working array of dimension 29. On exit with 'task' = NEW_X, the following information is available:

  • dsave(1) = current 'theta' in the BFGS matrix;
  • dsave(2) = f(x) in the previous iteration;
  • dsave(3) = factr*epsmch;
  • dsave(4) = 2-norm of the line search direction vector;
  • dsave(5) = the machine precision epsmch generated by the code;
  • dsave(7) = the accumulated time spent on searching for Cauchy points;
  • dsave(8) = the accumulated time spent on subspace minimization;
  • dsave(9) = the accumulated time spent on line search;
  • dsave(11) = the slope of the line search function at the current point of line search;
  • dsave(12) = the maximum relative step length imposed in line search;
  • dsave(13) = the infinity norm of the projected gradient;
  • dsave(14) = the relative step length in the line search;
  • dsave(15) = the slope of the line search function at the starting point of the line search;
  • dsave(16) = the square of the 2-norm of the line search direction vector.
character(len=*), intent(in), optional :: iteration_file

The name of the iteration file if used (Iprint>=1). If not specified, then 'iterate.dat' is used.


Calls

proc~~setulb~~CallsGraph proc~setulb lbfgsb_module::setulb proc~mainlb lbfgsb_module::mainlb proc~setulb->proc~mainlb proc~active lbfgsb_module::active proc~mainlb->proc~active proc~cauchy lbfgsb_module::cauchy proc~mainlb->proc~cauchy proc~cmprlb lbfgsb_module::cmprlb proc~mainlb->proc~cmprlb proc~dcopy lbfgsb_blas_module::dcopy proc~mainlb->proc~dcopy proc~ddot lbfgsb_blas_module::ddot proc~mainlb->proc~ddot proc~dscal lbfgsb_blas_module::dscal proc~mainlb->proc~dscal proc~errclb lbfgsb_module::errclb proc~mainlb->proc~errclb proc~formk lbfgsb_module::formk proc~mainlb->proc~formk proc~formt lbfgsb_module::formt proc~mainlb->proc~formt proc~freev lbfgsb_module::freev proc~mainlb->proc~freev proc~lnsrlb lbfgsb_module::lnsrlb proc~mainlb->proc~lnsrlb proc~matupd lbfgsb_module::matupd proc~mainlb->proc~matupd proc~prn1lb lbfgsb_module::prn1lb proc~mainlb->proc~prn1lb proc~prn2lb lbfgsb_module::prn2lb proc~mainlb->proc~prn2lb proc~prn3lb lbfgsb_module::prn3lb proc~mainlb->proc~prn3lb proc~projgr lbfgsb_module::projgr proc~mainlb->proc~projgr proc~subsm lbfgsb_module::subsm proc~mainlb->proc~subsm proc~cauchy->proc~dcopy proc~cauchy->proc~ddot proc~cauchy->proc~dscal proc~bmv lbfgsb_module::bmv proc~cauchy->proc~bmv proc~daxpy lbfgsb_blas_module::daxpy proc~cauchy->proc~daxpy proc~hpsolb lbfgsb_module::hpsolb proc~cauchy->proc~hpsolb proc~cmprlb->proc~bmv proc~formk->proc~dcopy proc~formk->proc~ddot proc~dpofa lbfgsb_linpack_module::dpofa proc~formk->proc~dpofa proc~dtrsl lbfgsb_linpack_module::dtrsl proc~formk->proc~dtrsl proc~formt->proc~dpofa proc~lnsrlb->proc~dcopy proc~lnsrlb->proc~ddot proc~dcsrch lbfgsb_module::dcsrch proc~lnsrlb->proc~dcsrch proc~matupd->proc~dcopy proc~matupd->proc~ddot proc~subsm->proc~dcopy proc~subsm->proc~dscal proc~subsm->proc~dtrsl proc~bmv->proc~dtrsl proc~dcstep lbfgsb_module::dcstep proc~dcsrch->proc~dcstep proc~dpofa->proc~ddot proc~dtrsl->proc~ddot proc~dtrsl->proc~daxpy

Source Code

      subroutine setulb(n,m,x,l,u,Nbd,f,g,Factr,Pgtol,Wa,Iwa,Task, &
                        Iprint,Csave,Lsave,Isave,Dsave,iteration_file)
      implicit none

      integer,intent(in) :: n !! the dimension of the problem (the number of variables).
      integer,intent(in) :: m !! the maximum number of variable metric corrections
                              !! used to define the limited memory matrix.
                              !! Values of `m < 3`  are
                              !! not recommended, and large values of `m` can result in excessive
                              !! computing time. The range  `3 <= m <= 20` is recommended.
      real(wp),intent(inout) :: x(n) !! On initial entry
                                     !! it must be set by the user to the values of the initial
                                     !! estimate of the solution vector.  Upon successful exit, it
                                     !! contains the values of the variables at the best point
                                     !! found (usually an approximate solution).
      real(wp),intent(in) :: l(n) !! the lower bound on `x`. If
                                  !! the `i`-th variable has no lower bound,
                                  !! `l(i)` need not be defined.
      real(wp),intent(in) :: u(n) !! the upper bound on `x`. If
                                  !! the `i`-th variable has no upper bound,
                                  !! `u(i)` need not be defined.
      integer,intent(in) :: Nbd(n) !! nbd represents the type of bounds imposed on the
                                   !! variables, and must be specified as follows:
                                   !!
                                   !!  * `nbd(i)=0` if `x(i)` is unbounded
                                   !!  * `nbd(i)=1` if `x(i)` has only a lower bound
                                   !!  * `nbd(i)=2` if `x(i)` has both lower and upper bounds
                                   !!  * `nbd(i)=3` if `x(i)` has only an upper bound
      real(wp),intent(inout) :: f !! On first entry `f` is unspecified.
                                  !! On final exit `f` is the value of the function at x.
                                  !! If the [[setulb]] returns
                                  !! with `task(1:2)= 'FG'`, then `f` must be set by the user to
                                  !! contain the value of the function at the point `x`.
      real(wp),intent(inout) :: g(n) !! On first entry `g` is unspecified.
                                     !! On final exit `g` is the value of the gradient at `x`.
                                     !! If the [[setulb]]
                                     !! returns with `task(1:2)= 'FG'`, then `g` must be set by the user to
                                     !! contain the components of the gradient at the point `x`.
      real(wp),intent(in) :: Factr !! A tolerance in the termination test for the algorithm.
                                   !! The iteration will stop when:
                                   !!
                                   !! `(f^k - f^{k+1})/max{|f^k|,|f^{k+1}|,1} <= factr*epsmch`
                                   !!
                                   !! where `epsmch` is the machine precision.
                                   !! Typical values for `factr` on a computer
                                   !! with 15 digits of accuracy in real(wp) are:
                                   !!
                                   !!  * `factr=1.0e+12` for low accuracy
                                   !!  * `factr=1.0e+7`  for moderate accuracy
                                   !!  * `factr=1.0e+1`  for extremely high accuracy
                                   !!
                                   !! The user can suppress this termination test by setting `factr=0`.
      real(wp),intent(in) :: Pgtol !! The iteration will stop when:
                                   !!
                                   !! `max{|proj g_i | i = 1, ..., n} <= pgtol`
                                   !!
                                   !! where `pg_i` is the `i`th component of the projected gradient.
                                   !! The user can suppress this termination test by setting `pgtol=0`.
      real(wp) :: Wa(2*m*n+5*n+11*m*m+8*m) !! working array of length `(2mmax + 5)nmax + 11mmax^2 + 8mmax`.
                                           !! This array must not be altered by the user.
      integer :: Iwa(3*n) !! an integer working array of length `3nmax`.
                          !! This array must not be altered by the user.
      character(len=60),intent(inout) :: Task !! Indicates the current job when entering and quitting this subroutine:
                                              !!
                                              !!  * On first entry, it must be set to 'START'.
                                              !!  * On a return with task(1:2)='FG', the user must evaluate the
                                              !!    function f and gradient g at the returned value of x.
                                              !!  * On a return with task(1:5)='NEW_X', an iteration of the
                                              !!    algorithm has concluded, and f and g contain f(x) and g(x)
                                              !!    respectively.  The user can decide whether to continue or stop
                                              !!    the iteration.
                                              !!  * When task(1:4)='CONV', the termination test in L-BFGS-B has been
                                              !!    satisfied;
                                              !!  * When task(1:4)='ABNO', the routine has terminated abnormally
                                              !!    without being able to satisfy the termination conditions,
                                              !!    x contains the best approximation found,
                                              !!    f and g contain f(x) and g(x) respectively;
                                              !!  * When task(1:5)='ERROR', the routine has detected an error in the
                                              !!    input parameters;
                                              !!
                                              !!  On exit with task = 'CONV', 'ABNO' or 'ERROR', the variable task
                                              !!  contains additional information that the user can print.
                                              !!
                                              !! This array should not be altered unless the user wants to
                                              !! stop the run for some reason.  See driver2 or driver3
                                              !! for a detailed explanation on how to stop the run
                                              !! by assigning task(1:4)='STOP' in the driver.
      integer,intent(in) :: Iprint !! Controls the frequency and type of output generated:
                                   !!
                                   !!  * `iprint<0   ` no output is generated
                                   !!  * `iprint=0   ` print only one line at the last iteration
                                   !!  * `0<iprint<99` print also `f` and `|proj g|` every `iprint` iterations
                                   !!  * `iprint=99  ` print details of every iteration except `n`-vectors
                                   !!  * `iprint=100 ` print also the changes of active set and final `x`
                                   !!  * `iprint>100 ` print details of every iteration including `x` and `g`
                                   !!
                                   !! When `iprint > 0`, the file `iterate.dat` will be created to
                                   !! summarize the iteration.
      character(len=60) :: Csave !! working string
      logical :: Lsave(4) !! A logical working array of dimension 4.
                          !! On exit with `task = 'NEW_X'`, the following information is available:
                          !!
                          !!  * If `lsave(1) = .true.` then the initial `x` did not satisfy the bounds
                          !!    and `x` has been replaced by its projection in the feasible set
                          !!  * If `lsave(2) = .true.` then the problem is constrained
                          !!  * If `lsave(3) = .true.` then each variable has upper and lower bounds
      integer :: Isave(44) !! An integer working array of dimension 44.
                           !! On exit with 'task' = NEW_X, the following information is available:
                           !!
                           !!  * isave(22) = the total number of intervals explored in the
                           !!    search of Cauchy points;
                           !!  * isave(26) = the total number of skipped BFGS updates before
                           !!    the current iteration;
                           !!  * isave(30) = the number of current iteration;
                           !!  * isave(31) = the total number of BFGS updates prior the current
                           !!    iteration;
                           !!  * isave(33) = the number of intervals explored in the search of
                           !!    Cauchy point in the current iteration;
                           !!  * isave(34) = the total number of function and gradient
                           !!    evaluations;
                           !!  * isave(36) = the number of function value or gradient
                           !!    evaluations in the current iteration;
                           !!  * if isave(37) = 0  then the subspace argmin is within the box;
                           !!  * if isave(37) = 1  then the subspace argmin is beyond the box;
                           !!  * isave(38) = the number of free variables in the current
                           !!    iteration;
                           !!  * isave(39) = the number of active constraints in the current
                           !!    iteration;
                           !!  * n + 1 - isave(40) = the number of variables leaving the set of
                           !!    active constraints in the current iteration;
                           !!  * isave(41) = the number of variables entering the set of active
                           !!    constraints in the current iteration.
      real(wp) :: Dsave(29) !! A real(wp) working array of dimension 29.
                            !! On exit with 'task' = NEW_X, the following information is available:
                            !!
                            !!  * dsave(1) = current 'theta' in the BFGS matrix;
                            !!  * dsave(2) = f(x) in the previous iteration;
                            !!  * dsave(3) = factr*epsmch;
                            !!  * dsave(4) = 2-norm of the line search direction vector;
                            !!  * dsave(5) = the machine precision epsmch generated by the code;
                            !!  * dsave(7) = the accumulated time spent on searching for
                            !!    Cauchy points;
                            !!  * dsave(8) = the accumulated time spent on
                            !!    subspace minimization;
                            !!  * dsave(9) = the accumulated time spent on line search;
                            !!  * dsave(11) = the slope of the line search function at
                            !!    the current point of line search;
                            !!  * dsave(12) = the maximum relative step length imposed in
                            !!    line search;
                            !!  * dsave(13) = the infinity norm of the projected gradient;
                            !!  * dsave(14) = the relative step length in the line search;
                            !!  * dsave(15) = the slope of the line search function at
                            !!    the starting point of the line search;
                            !!  * dsave(16) = the square of the 2-norm of the line search
                            !!    direction vector.
      character(len=*),intent(in),optional :: iteration_file !! The name of the iteration file if used (`Iprint>=1`).
                                                             !! If not specified, then 'iterate.dat' is used.

    integer :: lws , lr , lz , lt , ld , lxp , lwa , lwy , lsy , lss , &
               lwt , lwn , lsnd

      if ( Task=='START' ) then
         Isave(1) = m*n
         Isave(2) = m**2
         Isave(3) = 4*m**2
         Isave(4) = 1                       ! ws      m*n
         Isave(5) = Isave(4) + Isave(1)     ! wy      m*n
         Isave(6) = Isave(5) + Isave(1)     ! wsy     m**2
         Isave(7) = Isave(6) + Isave(2)     ! wss     m**2
         Isave(8) = Isave(7) + Isave(2)     ! wt      m**2
         Isave(9) = Isave(8) + Isave(2)     ! wn      4*m**2
         Isave(10) = Isave(9) + Isave(3)    ! wsnd    4*m**2
         Isave(11) = Isave(10) + Isave(3)   ! wz      n
         Isave(12) = Isave(11) + n          ! wr      n
         Isave(13) = Isave(12) + n          ! wd      n
         Isave(14) = Isave(13) + n          ! wt      n
         Isave(15) = Isave(14) + n          ! wxp     n
         Isave(16) = Isave(15) + n          ! wa      8*m
      endif
      lws = Isave(4)
      lwy = Isave(5)
      lsy = Isave(6)
      lss = Isave(7)
      lwt = Isave(8)
      lwn = Isave(9)
      lsnd = Isave(10)
      lz = Isave(11)
      lr = Isave(12)
      ld = Isave(13)
      lt = Isave(14)
      lxp = Isave(15)
      lwa = Isave(16)

      call mainlb(n,m,x,l,u,Nbd,f,g,Factr,Pgtol,Wa(lws),Wa(lwy),Wa(lsy),&
                  Wa(lss),Wa(lwt),Wa(lwn),Wa(lsnd),Wa(lz),Wa(lr),Wa(ld),&
                  Wa(lt),Wa(lxp),Wa(lwa),Iwa(1),Iwa(n+1),Iwa(2*n+1),    &
                  Task,Iprint,Csave,Lsave,Isave(22),Dsave,iteration_file)

      end subroutine setulb