lincoa_module Module

LINCOA: LINearly Constrained Optimization Algorithm

The purpose of LINCOA is to seek the least value of a function F of several variables subject to general linear inequality constraints on the variables, when derivatives of F are not available.

History

  • M.J.D. Powell, December 6th, 2013 : 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~~lincoa_module~~UsesGraph module~lincoa_module lincoa_module module~kind_module kind_module module~lincoa_module->module~kind_module iso_fortran_env iso_fortran_env module~kind_module->iso_fortran_env

Used by

  • module~~lincoa_module~~UsedByGraph module~lincoa_module lincoa_module module~powellopt powellopt module~powellopt->module~lincoa_module

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 lincoa(n, npt, m, a, ia, b, x, rhobeg, rhoend, iprint, maxfun, calfun)

This subroutine seeks the least value of a function of many variables,  subject to general linear inequality constraints, by a trust region  method that forms quadratic models by interpolation.

Read more…

Arguments

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

the number of variables. must be at least 2.

integer, intent(in) :: npt

the number of interpolation conditions, which is required to be in the interval [N+2,(N+1)(N+2)/2]. Typical choices of the author are NPT=N+6 and NPT=2*N+1. Larger values tend to be highly inefficent when the number of variables is substantial, due to the amount of work and extra difficulty of adjusting more points.

integer, intent(in) :: m

the number of linear inequality constraints.

real(kind=wp), intent(in), dimension(ia,*) :: a

a matrix whose columns are the constraint gradients, which are required to be nonzero.

integer, intent(in) :: ia

the first dimension of the array A, which must be at least N.

real(kind=wp), intent(in), dimension(*) :: b

the vector of right hand sides of the constraints, the J-th constraint being that the scalar product of A(.,J) with X(.) is at most B(J). The initial vector X(.) is made feasible by increasing the value of B(J) if necessary.

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

the vector of variables. Initial values of X(1),X(2),...,X(N) must be supplied. If they do not satisfy the constraints, then B is increased as mentioned above. X contains on return the variables that have given the least calculated F subject to the constraints.

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, the best feasible vector of variables so far and the corresponding value of the objective function are printed whenever RHO is reduced, where RHO is the current lower bound on the trust region radius. 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, its value being at least NPT+1.

procedure(func) :: calfun

It must set F to the value of the objective function for the variables X(1), X(2),...,X(N). The value of the argument F is positive when CALFUN is called if and only if the current X satisfies the constraints

private subroutine lincob(n, npt, m, amat, b, x, rhobeg, rhoend, iprint, maxfun, xbase, xpt, fval, xsav, xopt, gopt, hq, pq, bmat, zmat, ndim, step, sp, xnew, iact, rescon, qfac, rfac, pqw, w, calfun)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
integer :: m
real :: amat
real :: b
real :: x
real :: rhobeg
real :: rhoend
integer :: iprint
integer :: maxfun
real :: xbase
real :: xpt
real :: fval
real :: xsav
real :: xopt
real :: gopt
real :: hq
real :: pq
real :: bmat
real :: zmat
integer :: ndim
real :: step
real :: sp
real :: xnew
integer :: iact
real :: rescon
real :: qfac
real :: rfac
real :: pqw
real :: w
procedure(func) :: calfun

private subroutine getact(n, m, amat, b, nact, iact, qfac, rfac, snorm, resnew, resact, g, dw, vlam, w)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: m
real :: amat
real :: b
integer :: nact
integer :: iact
real :: qfac
real :: rfac
real :: snorm
real :: resnew
real :: resact
real :: g
real :: dw
real :: vlam
real :: w

private subroutine prelim(n, npt, m, amat, b, x, rhobeg, iprint, xbase, xpt, fval, xsav, xopt, gopt, kopt, hq, pq, bmat, zmat, idz, ndim, sp, rescon, step, pqw, w, calfun)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
integer :: m
real :: amat
real :: b
real :: x
real :: rhobeg
integer :: iprint
real :: xbase
real :: xpt
real :: fval
real :: xsav
real :: xopt
real :: gopt
integer :: kopt
real :: hq
real :: pq
real :: bmat
real :: zmat
integer :: idz
integer :: ndim
real :: sp
real :: rescon
real :: step
real :: pqw
real :: w
procedure(func) :: calfun

private subroutine qmstep(n, npt, m, amat, b, xpt, xopt, nact, iact, rescon, qfac, kopt, knew, del, step, gl, pqw, rstat, w, ifeas)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
integer :: m
real :: amat
real :: b
real :: xpt
real :: xopt
integer :: nact
integer :: iact
real :: rescon
real :: qfac
integer :: kopt
integer :: knew
real :: del
real :: step
real :: gl
real :: pqw
real :: rstat
real :: w
integer :: ifeas

private subroutine trstep(n, npt, m, amat, b, xpt, hq, pq, nact, iact, rescon, qfac, rfac, snorm, step, g, resnew, resact, d, dw, w)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
integer :: m
real :: amat
real :: b
real :: xpt
real :: hq
real :: pq
integer :: nact
integer :: iact
real :: rescon
real :: qfac
real :: rfac
real :: snorm
real :: step
real :: g
real :: resnew
real :: resact
real :: d
real :: dw
real :: w

private subroutine update(n, npt, xpt, bmat, zmat, idz, ndim, sp, step, kopt, knew, vlag, w)

Arguments

Type IntentOptional Attributes Name
integer :: n
integer :: npt
real :: xpt
real :: bmat
real :: zmat
integer :: idz
integer :: ndim
real :: sp
real :: step
integer :: kopt
integer :: knew
real :: vlag
real :: w

public subroutine lincoa_test()

Test problem for lincoa.

Read more…

Arguments

None