bobyqa_module Module

BOBYQA: Bound Optimization BY Quadratic Approximation

The purpose of BOBYQA is to seek the least value of a function F of several variables, when derivatives are not available. The constraints are the lower and upper bounds on every variable, which can be set to huge values for unconstrained variables.

The algorithm is intended to change the variables to values that are close to a local minimum of F. The user, however, should assume responsibility for finding out if the calculations are satisfactory, by considering carefully the values of F that occur.

References

History

  • M.J.D. Powell (January 5th, 2009) -- There are no restrictions on or charges for the use of the software. I hope that the time and effort I have spent on developing the package will be helpful to much research and to many applications.
  • Jacob Williams, July 2015 : refactoring of the code into modern Fortran.

Uses

  • module~~bobyqa_module~~UsesGraph module~bobyqa_module bobyqa_module module~kind_module kind_module module~bobyqa_module->module~kind_module iso_fortran_env iso_fortran_env module~kind_module->iso_fortran_env

Used by

  • module~~bobyqa_module~~UsedByGraph module~bobyqa_module bobyqa_module module~powellopt powellopt module~powellopt->module~bobyqa_module

Abstract Interfaces

abstract interface

  • private subroutine func(n, x, f)

    calfun interface

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: n
    real(kind=wp), intent(in), dimension(:) :: x
    real(kind=wp), intent(out) :: f

Subroutines

public subroutine bobyqa(n, npt, x, xl, xu, rhobeg, rhoend, iprint, maxfun, calfun)

This subroutine seeks the least value of a function of many variables, by applying a trust region method that forms quadratic models by interpolation. There is usually some freedom in the interpolation conditions, which is taken up by minimizing the Frobenius norm of the change to the second derivative of the model, beginning with the zero matrix. The values of the variables are constrained by upper and lower bounds.

Read more…

Arguments

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

number of variables (must be at least two)

integer, intent(in) :: npt

number of interpolation conditions. Its value must be in the interval [N+2,(N+1)(N+2)/2]. Choices that exceed 2*N+1 are not recommended.

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

Initial values of the variables must be set in X(1),X(2),...,X(N). They will be changed to the values that give the least calculated F.

real(kind=wp), intent(in), dimension(:) :: xl

lower bounds on x. The construction of quadratic models requires XL(I) to be strictly less than XU(I) for each I. Further, the contribution to a model from changes to the I-th variable is damaged severely by rounding errors if XU(I)-XL(I) is too small.

real(kind=wp), intent(in), dimension(:) :: xu

upper bounds on x. The construction of quadratic models requires XL(I) to be strictly less than XU(I) for each I. Further, the contribution to a model from changes to the I-th variable is damaged severely by rounding errors if XU(I)-XL(I) is too small.

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

RHOBEG must be set to the initial value of a trust region radius. It must be positive, and typically should be about one tenth of the greatest expected change to a variable. An error return occurs if any of the differences XU(I)-XL(I), I=1,...,N, is less than 2*RHOBEG.

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

RHOEND must be set to the final value of a trust region radius. It must be positive with RHOEND no greater than RHOBEG. Typically, RHOEND should indicate the accuracy that is required in the final values of the variables.

integer, intent(in) :: iprint

IPRINT should be set to 0, 1, 2 or 3, which controls the amount of printing. Specifically, there is no output if IPRINT=0 and there is output only at the return if IPRINT=1. Otherwise, each new value of RHO is printed, with the best vector of variables so far and the corresponding value of the objective function. Further, each new value of F with its variables are output if IPRINT=3.

integer, intent(in) :: maxfun

an upper bound on the number of calls of CALFUN.

procedure(func) :: calfun

SUBROUTINE CALFUN (N,X,F) has to be provided by the user. It must set F to the value of the objective function for the current values of the variables X(1),X(2),...,X(N), which are generated automatically in a way that satisfies the bounds given in XL and XU.

private subroutine bobyqb(n, npt, x, xl, xu, rhobeg, rhoend, iprint, maxfun, xbase, xpt, fval, xopt, gopt, hq, pq, bmat, zmat, ndim, sl, su, xnew, xalt, d, vlag, w, calfun)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: x
real :: xl
real :: xu
real :: rhobeg
real :: rhoend
integer :: iprint
integer :: maxfun
real :: xbase
real :: xpt
real :: fval
real :: xopt
real :: gopt
real :: hq
real :: pq
real :: bmat
real :: zmat
integer :: ndim
real :: sl
real :: su
real :: xnew
real :: xalt
real :: d
real :: vlag
real :: w
procedure(func) :: calfun

private subroutine altmov(n, npt, xpt, xopt, bmat, zmat, ndim, sl, su, kopt, knew, adelt, xnew, xalt, alpha, cauchy, glag, hcol, w)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: xpt
real :: xopt
real :: bmat
real :: zmat
integer :: ndim
real :: sl
real :: su
integer :: kopt
integer :: knew
real :: adelt
real :: xnew
real :: xalt
real :: alpha
real :: cauchy
real :: glag
real :: hcol
real :: w

private subroutine prelim(n, npt, x, xl, xu, rhobeg, iprint, maxfun, xbase, xpt, fval, gopt, hq, pq, bmat, zmat, ndim, sl, su, nf, kopt, calfun)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: x
real :: xl
real :: xu
real :: rhobeg
integer :: iprint
integer :: maxfun
real :: xbase
real :: xpt
real :: fval
real :: gopt
real :: hq
real :: pq
real :: bmat
real :: zmat
integer :: ndim
real :: sl
real :: su
integer :: nf
integer :: kopt
procedure(func) :: calfun

private subroutine rescue(n, npt, xl, xu, iprint, maxfun, xbase, xpt, fval, xopt, gopt, hq, pq, bmat, zmat, ndim, sl, su, nf, delta, kopt, vlag, ptsaux, ptsid, w, calfun)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: xl
real :: xu
integer :: iprint
integer :: maxfun
real :: xbase
real :: xpt
real :: fval
real :: xopt
real :: gopt
real :: hq
real :: pq
real :: bmat
real :: zmat
integer :: ndim
real :: sl
real :: su
integer :: nf
real :: delta
integer :: kopt
real :: vlag
real :: ptsaux
real :: ptsid
real :: w
procedure(func) :: calfun

private subroutine trsbox(n, npt, xpt, xopt, gopt, hq, pq, sl, su, delta, xnew, d, gnew, xbdi, s, hs, hred, dsq, crvmin)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: xpt
real :: xopt
real :: gopt
real :: hq
real :: pq
real :: sl
real :: su
real :: delta
real :: xnew
real :: d
real :: gnew
real :: xbdi
real :: s
real :: hs
real :: hred
real :: dsq
real :: crvmin

private subroutine update(n, npt, bmat, zmat, ndim, vlag, beta, denom, knew, w)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: bmat
real :: zmat
integer :: ndim
real :: vlag
real :: beta
real :: denom
integer :: knew
real :: w

public subroutine bobyqa_test()

Test problem for bobyqa, the objective function being the sum of the reciprocals of all pairwise distances between the points P_I, I=1,2,...,M in two dimensions, where M=N/2 and where the components of P_I are X(2I-1) and X(2I). Thus each vector X of N variables defines the M points P_I. The initial X gives equally spaced points on a circle. Four different choices of the pairs (N,NPT) are tried, namely (10,16), (10,21), (20,26) and (20,41). Convergence to a local minimum that is not global occurs in both the N=10 cases. The details of the results are highly sensitive to computer rounding errors. The choice IPRINT=2 provides the current X and optimal F so far whenever RHO is reduced. The bound constraints of the problem require every component of X to be in the interval [-1,1].

Arguments

None