uobyqa_module Module

UOBYQA: Unconstrained Optimization BY Quadratic Approximation

The purpose of UOBYQA is to seek the least value of a function F of several variables, when derivatives are not available. It uses a trust region method that forms quadratic models by interpolation.

References

History

  • M.J.D. Powell : It is hoped that the software will be helpful to much future research and to many applications. There are no restrictions on or charges for its use.
  • Jacob Williams, July 2015 : refactoring of the code into modern Fortran.

Uses

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

Used by

  • module~~uobyqa_module~~UsedByGraph module~uobyqa_module uobyqa_module module~powellopt powellopt module~powellopt->module~uobyqa_module

Variables

Type Visibility Attributes Name Initial
real(kind=wp), private, parameter :: half = 0.5_wp
real(kind=wp), private, parameter :: one = 1.0_wp
real(kind=wp), private, parameter :: tenth = 0.1_wp
real(kind=wp), private, parameter :: zero = 0.0_wp
real(kind=wp), private, parameter :: quart = 0.25_wp
real(kind=wp), private, parameter :: two = 2.0_wp
real(kind=wp), private, parameter :: halfrt = sqrt(half)

Abstract Interfaces

abstract interface

  • private subroutine func(n, x, f)

    calfun interface

    Arguments

    Type IntentOptional Attributes Name
    integer :: n
    real(kind=wp) :: x(*)
    real(kind=wp) :: f

Subroutines

public subroutine uobyqa(n, x, rhobeg, rhoend, iprint, maxfun, calfun)

This subroutine seeks the least value of a function of many variables, by a trust region method that forms quadratic models by interpolation.

Arguments

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

the number of variables and must be at least two

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) :: rhobeg

RHOBEG and RHOEND must be set to the initial and final values of a trust region radius, so both must be positive with RHOEND<=RHOBEG. Typically RHOBEG should be about one tenth of the greatest expected change to a variable, and RHOEND should indicate the accuracy that is required in the final values of the variables.

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

RHOBEG and RHOEND must be set to the initial and final values of a trust region radius, so both must be positive with RHOEND<=RHOBEG. Typically RHOBEG should be about one tenth of the greatest expected change to a variable, and RHOEND should indicate the accuracy that is required in the final values of the variables.

integer, intent(in) :: iprint

The value of 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

upper bound on the number of calls of CALFUN.

procedure(func) :: calfun

It must set F to the value of the objective function for the variables X(1),X(2),...,X(N).

private subroutine uobyqb(n, x, rhobeg, rhoend, iprint, maxfun, npt, xbase, xopt, xnew, xpt, pq, pl, h, g, d, vlag, w, calfun)

Arguments

Type IntentOptional Attributes Name
integer :: n
real :: x
real :: rhobeg
real :: rhoend
integer :: iprint
integer :: maxfun
integer :: npt
real :: xbase
real :: xopt
real :: xnew
real :: xpt
real :: pq
real :: pl
real :: h
real :: g
real :: d
real :: vlag
real :: w
procedure(func) :: calfun

private subroutine lagmax(n, g, h, rho, d, v, vmax)

Arguments

Type IntentOptional Attributes Name
integer :: n
real :: g
real :: h
real :: rho
real :: d
real :: v
real :: vmax

private subroutine trstep(n, g, h, delta, tol, d, gg, td, tn, w, piv, z, evalue)

Arguments

Type IntentOptional Attributes Name
integer :: n
real :: g
real :: h
real :: delta
real :: tol
real :: d
real :: gg
real :: td
real :: tn
real :: w
real :: piv
real :: z
real :: evalue

public subroutine uobyqa_test()

The Chebyquad test problem (Fletcher, 1965) for N = 2,4,6,8.

Arguments

None