optgra Derived Type

type, public :: optgra

Main class for OPTGRA algorithm.

The main methods are initialize, solve, and destroy.


Components

Type Visibility Attributes Name Initial
integer(kind=ip), private :: numvar = 0

number of variables

real(kind=wp), private, dimension(: ), allocatable :: varval
integer(kind=ip), private, dimension(: ), allocatable :: vartyp
real(kind=wp), private, dimension(: ), allocatable :: varsca
character(len=name_len), private, dimension(: ), allocatable :: varstr
integer(kind=ip), private, dimension(: ), allocatable :: varlen
real(kind=wp), private, dimension(: ), allocatable :: varref
real(kind=wp), private, dimension(: ), allocatable :: vardes
real(kind=wp), private, dimension(: ), allocatable :: vargrd
real(kind=wp), private, dimension(: ), allocatable :: vardir
real(kind=wp), private, dimension(: ), allocatable :: funvar
real(kind=wp), private, dimension(: ), allocatable :: senvar
integer(kind=ip), private :: numcon = 0

number of constraints

real(kind=wp), private, dimension(: ), allocatable :: conval
integer(kind=ip), private, dimension(: ), allocatable :: contyp
integer(kind=ip), private, dimension(: ), allocatable :: conpri
real(kind=wp), private, dimension(: ), allocatable :: consca
character(len=name_len), private, dimension(: ), allocatable :: constr
integer(kind=ip), private, dimension(: ), allocatable :: conlen
real(kind=wp), private, dimension(: ), allocatable :: conref
real(kind=wp), private, dimension(: ), allocatable :: senqua
real(kind=wp), private, dimension(: ), allocatable :: sencon
real(kind=wp), private, dimension(: ), allocatable :: sendel
integer(kind=ip), private, dimension(: ), allocatable :: senact
integer(kind=ip), private :: optmet = 2

optimization method

integer(kind=ip), private :: maxite = 10

maximum number of iterations

integer(kind=ip), private :: corite = 10
integer(kind=ip), private :: optite = 10
integer(kind=ip), private :: divite = 10
integer(kind=ip), private :: cnvite = 10
real(kind=wp), private :: Varmax = 10.0_wp

maximum distance per iteration

real(kind=wp), private :: varsnd = 1.0_wp

perturbation for 2nd order derivatives

real(kind=wp), private :: varstp = 1.0_wp
integer(kind=ip), private :: varder = 1

derivatives computation mode

real(kind=wp), private, dimension(: ), allocatable :: varper
integer(kind=ip), private :: loglun = output_unit

log file unit

integer(kind=ip), private :: loglev = 1

log level

integer(kind=ip), private :: loglup = output_unit

pygmo log file unit

integer(kind=ip), private :: verbos = 0

pygmo verbosity

integer(kind=ip), private :: fevals = 0

pygmo: number of const fun evals

integer(kind=ip), private :: pygfla = 0

pygmo: flag indicating status of optimization

integer(kind=ip), private :: numite = 0

number of iterations

integer(kind=ip), private :: matlev = 0
integer(kind=ip), private :: tablun = output_unit

logical unit for writing table

integer(kind=ip), private :: tablev = 0

level of tab

integer(kind=ip), private :: senopt = 0

sensitivity optimization mode

integer(kind=ip), private :: numact = 0
integer(kind=ip), private, dimension(: ), allocatable :: actcon
integer(kind=ip), private, dimension(: ), allocatable :: confix
integer(kind=ip), private, dimension(: ), allocatable :: conact
real(kind=wp), private, dimension(:,:), allocatable :: conder
real(kind=wp), private, dimension(:,:), allocatable :: conred
real(kind=wp), private, dimension(:,:), allocatable :: sender
procedure(calval_f), private, pointer :: calval => null()

function for values

procedure(calder_f), private, pointer :: calder => null()

function for derivatives


Type-Bound Procedures

procedure, public :: initialize

set up the problem

  • private subroutine initialize(me, Numvar, Numcon, Calval, Calder, Delcon, Conpri, Consca, Constr, Conlen, Contyp, Varder, Varper, Varmax, Varsnd, Maxite, Itecor, Iteopt, Itediv, Itecnv, Loglup, Verbos, Senopt, Varsca, Varstr, Varlen, Vartyp, Loglun, Loglev, Matlev, Tablun, Tablev, Optmet)

    Initialize the class. This should be the first routine called.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(out) :: me
    integer(kind=ip), intent(in) :: Numvar

    NUMBER OF VARIABLES

    integer(kind=ip), intent(in) :: Numcon

    NUMBER OF CONSTRAINTS

    procedure(calval_f) :: Calval

    FUNCTION FOR VALUES -> INPUT AND OUTPUT NOT SCALED

    procedure(calder_f) :: Calder

    FUNCTION FOR VALUES AND DERIVATIVES -> INPUT AND OUTPUT NOT SCALED

    real(kind=wp), intent(in) :: Delcon(Numcon+1)

    CONSTRAINTS DELTAS (CONSTRAINT + MERIT CONVERGENCE THRESHOLDS)

    integer(kind=ip), intent(in) :: Conpri(Numcon+1)

    CONSTRAINTS PRIORITY (1:NUMCON) -> 1-N

    Read more…
    real(kind=wp), intent(in) :: Consca(Numcon+1) Read more…
    character(len=name_len), intent(in) :: Constr(Numcon+1)

    CONIABLES NAME STRING

    integer(kind=ip), intent(in) :: Conlen(Numcon+1)

    CONIABLES NAME LENGTH

    integer(kind=ip), intent(in) :: Contyp(Numcon+1)

    CONSTRAINTS TYPE (1:NUMCON)

    Read more…
    integer(kind=ip), intent(in) :: Varder

    DERIVATIVES COMPUTATION MODE

    Read more…
    real(kind=wp), intent(in) :: Varper(Numvar)

    VARIABLES PERTURBATION FOR DERIVATIVES -> NOT SCALED

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

    MAXIMUM DISTANCE PER ITERATION -> SCALED

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

    PERTURBATION FOR 2ND ORDER DERIVATIVES -> SCALED

    integer(kind=ip), intent(in) :: Maxite

    maximum number of iterations

    integer(kind=ip), intent(in) :: Itecor

    number of constraint correction iterations in the beginning. If no feasible solution is found within that many iterations, Optgra aborts

    integer(kind=ip), intent(in) :: Iteopt

    some other iter input ?

    integer(kind=ip), intent(in) :: Itediv

    some other iter input ?

    integer(kind=ip), intent(in) :: Itecnv

    some other iter input ?

    integer(kind=ip), intent(in) :: Loglup

    LOGICAL UNIT FOR WRITING PYGMO LOG

    integer(kind=ip), intent(in) :: Verbos

    VERBOSITY LEVEL:

    Read more…
    integer(kind=ip), intent(in) :: Senopt

    sensitivity optimization mode

    Read more…
    real(kind=wp), intent(in) :: Varsca(Numvar)

    VARIABLES SCALE FACTOR

    character(len=name_len), intent(in) :: Varstr(Numvar)

    VARIABLES NAME STRING

    integer(kind=ip), intent(in) :: Varlen(Numvar)

    VARIABLES NAME LENGTH

    integer(kind=ip), intent(in) :: Vartyp(Numvar)

    VARIABLES TYPE

    Read more…
    integer(kind=ip), intent(in) :: Loglun

    LOGICAL UNIT FOR WRITING LOG

    integer(kind=ip), intent(in) :: Loglev

    LEVEL OF LOG:

    Read more…
    integer(kind=ip), intent(in) :: Matlev

    LEVEL OF LOG:

    Read more…
    integer(kind=ip), intent(in) :: Tablun

    logical unit for writing table

    integer(kind=ip), intent(in) :: Tablev

    LEVEL OF TAB

    Read more…
    integer(kind=ip), intent(in) :: Optmet

    OPTIMIZATION METHOD:

    Read more…

procedure, public :: solve => ogexec

solve the problem

  • private subroutine ogexec(me, Valvar, Valcon, Finopt, Finite)

    Main routine.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(inout) :: Valvar(me%Numvar)

    VARIABLES VALUE -> NOT SCALED

    real(kind=wp), intent(out) :: Valcon(me%Numcon+1)

    CONSTRAINTS VALUE (1:NUMCON) MERIT VALUE (1+NUMCON) -> NOT SCALED

    integer(kind=ip), intent(out) :: Finopt

    TERMINATION STATUS

    Read more…
    integer(kind=ip), intent(out) :: Finite

    ?

procedure, public :: destroy => ogclos

free memory when finished

  • private subroutine ogclos(me)

    DEALLOCATION OF ARRAYS

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me

procedure, public :: ogsens

  • private subroutine ogsens(me, Consta, Concon, Convar, Varcon, Varvar)

    NEAR-LINEAR OPTIMIZATION TOOL SENSITIVITY ANALYSIS

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    integer(kind=ip), intent(out) :: Consta(me%Numcon)

    CONSTRAINT STATUS (0=PAS 1=ACT)

    real(kind=wp), intent(out) :: Concon(me%Numcon+1,me%Numcon)

    SENSITIVITY OF CONTRAINTS+MERIT W.R.T. ACTIVE CONSTRAINTS

    real(kind=wp), intent(out) :: Convar(me%Numcon+1,me%Numvar)

    SENSITIVITY OF CONTRAINTS+MERIT W.R.T. PARAMETERS

    real(kind=wp), intent(out) :: Varcon(me%Numvar,me%Numcon)

    SENSITIVITY OF VARIABLES W.R.T. ACTIVE CONSTRAINTS

    real(kind=wp), intent(out) :: Varvar(me%Numvar,me%Numvar)

    SENSITIVITY OF VARIABLES W.R.T. PARAMETERS -> NOT SCALED

procedure, public :: ogssst

  • private subroutine ogssst(me, Varsen, Quasen, Consen, Actsen, Dersen, Actsav, Consav, Redsav, Dersav, Actnum)

    NEAR-LINEAR OPTIMIZATION TOOL SENSITIVITY ANALYSIS

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(in) :: Varsen(me%Numvar)

    STORED VARIABLES VALUE

    real(kind=wp), intent(in) :: Quasen(me%Numcon+1)

    STORED CONSTRAINTS CORRECTION VECTOR

    real(kind=wp), intent(in) :: Consen(me%Numcon+1)

    STORED CONSTRAINTS VALUE

    integer(kind=ip), intent(in) :: Actsen(me%Numcon+1)

    STORED CONSTRAINTS ACTIVE

    real(kind=wp), intent(in) :: Dersen(me%Numcon+1,me%Numvar)

    STORED DERIVATIVE

    integer(kind=ip), intent(in) :: Actsav(me%Numcon+1)

    STORED ACTIVE CONSTRAINTS

    integer(kind=ip), intent(in) :: Consav(me%Numcon+4)

    STORED ACTIVE CONSTRAINTS

    real(kind=wp), intent(in) :: Redsav(me%Numcon+3,me%Numvar)

    STORED DERIVATIVE

    real(kind=wp), intent(in) :: Dersav(me%Numcon+3,me%Numvar)

    STORED DERIVATIVE

    integer(kind=ip), intent(in) :: Actnum

procedure, public :: oggsst

  • private subroutine oggsst(me, Varsen, Quasen, Consen, Actsen, Dersen, Actsav, Consav, Redsav, Dersav, Actnum)

    NEAR-LINEAR OPTIMIZATION TOOL SENSITIVITY ANALYSIS

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(out) :: Varsen(me%Numvar)

    STORED VARIABLES VALUE

    real(kind=wp), intent(out) :: Quasen(me%Numcon+1)

    STORED CONSTRAINTS CORRECTION VECTOR

    real(kind=wp), intent(out) :: Consen(me%Numcon+1)

    STORED CONSTRAINTS VALUE

    integer(kind=ip), intent(out) :: Actsen(me%Numcon+1)

    STORED CONSTRAINTS ACTIVE

    real(kind=wp), intent(out) :: Dersen(me%Numcon+1,me%Numvar)

    STORED DERIVATIVE

    integer(kind=ip), intent(out) :: Actsav(me%Numcon+1)

    STORED ACTIVE CONSTRAINTS

    integer(kind=ip), intent(out) :: Consav(me%Numcon+4)

    STORED ACTIVE CONSTRAINTS

    real(kind=wp), intent(out) :: Redsav(me%Numcon+3,me%Numvar)

    STORED DERIVATIVE

    real(kind=wp), intent(out) :: Dersav(me%Numcon+3,me%Numvar)

    STORED DERIVATIVE

    integer(kind=ip), intent(out) :: Actnum

    NUMBER OF ACTIVE CONSTRAINTS

procedure, private :: ogrigt

  • private function ogrigt(me, Actinp) result(Actout)

    RIGHT-MULTIPLIES VECTOR LOWER TRIANGULAR MATRIX OBTAINED BY REDUCTION AND SUBSEQUENT INVERSION OF DERIVATIVES OF ACTIVE CONSTRAINTS

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(in) :: Actinp(me%Numcon)

    VECTOR INITAL

    Return Value real(kind=wp), (me%Numcon)

    VECTOR FINAL

procedure, private :: ogincl

  • private subroutine ogincl(me, Inc)

    ADDS CONSTRAINT TO ACTIVE SET AND REDUCES DERIVATIVES

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    integer(kind=ip), intent(in) :: Inc

    CONSTRAINT TO BE INCLUDED

procedure, private :: ogexcl

  • private subroutine ogexcl(me, Exc, error)

    REMOVE CONSTRAINT TO ACTIVE SET AND REDUCES DERIVATIVES

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    integer(kind=ip), intent(in) :: Exc

    CONSTRAINT TO BE REMOVED SEQUENCE NUMBER IN ACTIVE LIST

    logical, intent(out) :: error

    if there was a fatal error (constraints singular)

procedure, private :: ogeval

  • private subroutine ogeval(me, Valvar, Valcon, Varder, Dercon)

    COMPUTES SCALED CONTRAINTS+MERIT AND DERIVATIVES FROM SCALED VARIABLES

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(in) :: Valvar(me%Numvar)

    SCALED VARIABLES: valvar(var) = x_var / varsca(var)

    real(kind=wp), intent(out) :: Valcon(me%Numcon+1)

    SCALED CONTRAINTS+MERIT AND DERIVATIVES:

    Read more…
    integer(kind=ip), intent(in) :: Varder

    DERIVATIVES COMPUTATION MODE

    Read more…
    real(kind=wp), intent(out) :: Dercon(me%Numcon+1,me%Numvar)

    derivatives of scaled valcon w.r.t. scaled valvar: dercon(con,var) = d(valcon(con))/d(valvar(var))

    Read more…

procedure, private :: ogcorr

  • private subroutine ogcorr(me, Varacc, Finish, Toterr, Norerr, error)

    CORRECTION PART

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(inout) :: Varacc
    integer(kind=ip), intent(out) :: Finish
    real(kind=wp) :: Toterr
    real(kind=wp) :: Norerr
    logical, intent(out) :: error

    if there was a fatal error

procedure, private :: ogopti

  • private subroutine ogopti(me, Varacc, Finish, Desnor, error)

    OPTIMIZATION PART

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(inout) :: Varacc

    ITERATION SCALED DISTANCE ACCUMULATED

    integer(kind=ip), intent(out) :: Finish

    0=LIMIT 1=OPTIM

    real(kind=wp) :: Desnor
    logical, intent(out) :: error

    if there was a fatal error

procedure, private :: ogleft

  • private function ogleft(me, Actinp) result(Actout)

    LEFT-MULTIPLIES VECTOR LOWER TRIANGULAR MATRIX OBTAINED BY REDUCTION AND SUBSEQUENT INVERSION OF DERIVATIVES OF ACTIVE CONSTRAINTS

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(in) :: Actinp(me%Numcon)

    VECTOR INITAL

    Return Value real(kind=wp), (me%Numcon)

    VECTOR FINAL

procedure, private :: ogpwri

  • private subroutine ogpwri(me, Objval, Numvio, Convio)

    WRITE OPTIMIZATION LOG IN PYGMO FORMAT

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(in) :: Objval

    OBJECTIVE VALUE

    integer(kind=ip), intent(in) :: Numvio

    NUMBER OF VIOLATED CONSTRAINTS

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

    TOTAL CONSTRAINT VIOLATION

procedure, private :: ogwrit

  • private subroutine ogwrit(me, Lev, Str)

    Write a message to the log.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    integer(kind=ip), intent(in) :: Lev

    only print if Loglev is >= this

    character(len=*), intent(in) :: Str

    string to print

procedure, private :: ogpwri_start

  • private subroutine ogpwri_start(me)

    WRITE OPTIMIZATION LOG IN PYGMO FORMAT

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me

procedure, private :: ogpwri_end

  • private subroutine ogpwri_end(me, Objval, Numvio, Convio)

    WRITE OPTIMIZATION END RESULT IN PYGMO FORMAT

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(optgra), intent(inout) :: me
    real(kind=wp), intent(in) :: Objval

    OBJECTIVE VALUE

    integer(kind=ip), intent(in) :: Numvio

    NUMBER OF VIOLATED CONSTRAINTS

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

    TOTAL CONSTRAINT VIOLATION

Source Code

   type,public :: optgra
      !! Main class for OPTGRA algorithm.
      !!
      !! The main methods are [[optgra:initialize]], [[optgra:solve]], and [[optgra:destroy]].

      private

      integer(ip) :: numvar = 0 !! number of variables
      real(wp),      dimension(:  ), allocatable :: varval
      integer(ip),   dimension(:  ), allocatable :: vartyp
      real(wp),      dimension(:  ), allocatable :: varsca
      character(len=name_len),    dimension(:  ), allocatable :: varstr
      integer(ip),   dimension(:  ), allocatable :: varlen
      real(wp),      dimension(:  ), allocatable :: varref
      real(wp),      dimension(:  ), allocatable :: vardes
      real(wp),      dimension(:  ), allocatable :: vargrd
      real(wp),      dimension(:  ), allocatable :: vardir
      real(wp),      dimension(:  ), allocatable :: funvar
      real(wp),      dimension(:  ), allocatable :: senvar

      integer(ip) :: numcon = 0 !! number of constraints
      real(wp),      dimension(:  ), allocatable :: conval
      integer(ip),   dimension(:  ), allocatable :: contyp
      integer(ip),   dimension(:  ), allocatable :: conpri
      real(wp),      dimension(:  ), allocatable :: consca
      character(len=name_len),    dimension(:  ), allocatable :: constr
      integer(ip),   dimension(:  ), allocatable :: conlen
      real(wp),      dimension(:  ), allocatable :: conref
      real(wp),      dimension(:  ), allocatable :: senqua
      real(wp),      dimension(:  ), allocatable :: sencon
      real(wp),      dimension(:  ), allocatable :: sendel
      integer(ip),   dimension(:  ), allocatable :: senact

      integer(ip)  :: optmet = 2 !! optimization method
      integer(ip)  :: maxite = 10 !! maximum number of iterations
      integer(ip)  :: corite = 10
      integer(ip)  :: optite = 10
      integer(ip)  :: divite = 10
      integer(ip)  :: cnvite = 10
      real(wp)     :: Varmax = 10.0_wp !! maximum distance per iteration
      real(wp)     :: varsnd = 1.0_wp !! perturbation for 2nd order derivatives
      real(wp)     :: varstp = 1.0_wp

      integer(ip) :: varder = 1 !! derivatives computation mode
      real(wp),      dimension(:  ), allocatable :: varper

      integer(ip) :: loglun = output_unit  !! log file unit
      integer(ip) :: loglev = 1  !! log level

      integer(ip) :: loglup = output_unit  !! pygmo log file unit
      integer(ip) :: verbos = 0  !! pygmo verbosity
      integer(ip) :: fevals = 0  !! pygmo: number of const fun evals
      integer(ip) :: pygfla = 0  !! pygmo: flag indicating status of optimization
      integer(ip) :: numite = 0  !! number of iterations

      integer(ip) :: matlev = 0

      integer(ip) :: tablun = output_unit !! logical unit for writing table
      integer(ip) :: tablev = 0 !! level of tab

      integer(ip) :: senopt = 0 !! sensitivity optimization mode

      integer(ip) :: numact = 0
      integer(ip),   dimension(:  ), allocatable :: actcon
      integer(ip),   dimension(:  ), allocatable :: confix
      integer(ip),   dimension(:  ), allocatable :: conact
      real(wp),      dimension(:,:), allocatable :: conder
      real(wp),      dimension(:,:), allocatable :: conred
      real(wp),      dimension(:,:), allocatable :: sender
      !integer(ip) :: CONVER = 0   ! not used ?
      !integer(ip),   DIMENSION(:  ), allocatable :: CONOPT  ! not used ?

      procedure(calval_f),pointer :: calval => null() !! function for values
      procedure(calder_f),pointer :: calder => null() !! function for derivatives

   contains

      private

      procedure,public :: initialize !! set up the problem
      procedure,public :: solve => ogexec !! solve the problem
      procedure,public :: destroy => ogclos !! free memory when finished

      ! are these intented to be user callable?
      procedure,public :: ogsens
      procedure,public :: ogssst
      procedure,public :: oggsst

      ! private methods:
      procedure :: ogrigt
      procedure :: ogincl
      procedure :: ogexcl
      procedure :: ogeval
      procedure :: ogcorr
      procedure :: ogopti
      procedure :: ogleft
      procedure :: ogpwri
      procedure :: ogwrit
      procedure :: ogpwri_start
      procedure :: ogpwri_end

   end type optgra