conmax_solver Derived Type

type, public, abstract :: conmax_solver

main CONMAX solver class. This class must be extended to define the users's fnset function.


Type-Bound Procedures

procedure, public :: solve => conmax

main solver routine

  • private subroutine conmax(me, ioptn, nparm, numgr, itlim, fun, ifun, pttbl, iptb, Indm, iwork, liwrk, work, lwrk, iter, param, error)

    CONMAX consists of two programs for solving the problem

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer, intent(in) :: ioptn

    THIS IS THE OPTION SWITCH, WHICH SHOULD BE SET TO 0 UNLESS ONE OR MORE OF THE EXTRA OPTIONS DESCRIBED BELOW IS USED. THE USER HAS SEVERAL EXTRA OPTIONS WHICH ARE ACTIVATED BY SETTING IOPTN TO A VALUE OTHER THAN 0; MORE THAN ONE AT A TIME CAN BE USED. IN PARTICULAR:

    Read more…
    integer, intent(in) :: nparm

    THIS IS THE NUMBER OF PARAMETERS IN THE PROBLEM. (THEY ARE STORED IN PARAM -- SEE BELOW.)

    integer, intent(in) :: numgr

    THIS IS THE TOTAL NUMBER OF CONSTRAINTS.

    integer, intent(in) :: itlim

    THIS IS THE LIMIT ON THE NUMBER OF ITERATIONS, I.E. THE LIMIT ON THE NUMBER OF TIMES THE PROGRAM REDUCES W. IF ITLIM IS SET TO 0 THE PROGRAM WILL COMPUTE THE ERRORS FOR THE INITIAL APPROXIMATION AND STOP WITHOUT CHECKING FEASIBILITY.

    real(kind=wp), intent(in) :: fun(Ifun)

    (VECTOR ARRAY OF DIMENSION IFUN) THIS IS A VECTOR ARRAY IN WHICH DATA OR FUNCTION VALUES IN TYPE 2 CONSTRAINTS (SEE ABOVE) CAN BE STORED. FUN(I) NEED NOT BE ASSIGNED A VALUE IF IT IS NOT GOING TO BE USED.

    integer, intent(in) :: ifun

    THIS IS THE DIMENSION OF FUN IN THE DRIVER PROGRAM. IT MUST BE >= THE LARGEST INDEX I FOR WHICH FUN(I) IS USED UNLESS NO FUN(I) IS USED, IN WHICH CASE IT MUST BE >= 1.

    real(kind=wp), intent(in) :: pttbl(Iptb,Indm)

    (MATRIX ARRAY OF DIMENSION (IPTB,INDM)) ROW I OF THIS ARRAY NORMALLY CONTAINS A POINT USED IN THE ITH CONSTRAINT. THE ENTRIES IN ROW I NEED NOT BE ASSIGNED VALUES IF SUCH A POINT IS NOT USED IN THE ITH CONSTRAINT. (EXAMPLE: IF THE LEFT SIDE OF CONSTRAINT I IS A POLYNOMIAL IN ONE INDEPENDENT VARIABLE, THEN THE VALUE OF THE INDEPENDENT VARIABLE SHOULD BE IN PTTBL(I,1), AND THE COEFFICIENTS SHOULD BE IN PARAM.) PTTBL CAN ALSO BE USED TO PASS OTHER INFORMATION FROM THE DRIVER PROGRAM TO SUBROUTINE FNSET.

    integer, intent(in) :: iptb

    THIS IS THE FIRST DIMENSION OF PTTBL IN THE DRIVER PROGRAM. IT MUST BE >= THE LARGEST SUBSCRIPT I FOR WHICH A VALUE PTTBL(I,J) IS USED, AND MUST BE >= 1 IF NO SUCH VALUES ARE USED.

    integer, intent(in) :: Indm

    THIS IS THE SECOND DIMENSION OF PTTBL IN THE DRIVER PROGRAM. IT MUST BE >= THE LARGEST SUBSCRIPT J FOR WHICH A VALUE PTTBL(I,J) IS USED, AND MUST BE >= 1 IF NO SUCH VALUES ARE USED.

    integer, intent(inout) :: iwork(Liwrk)

    (VECTOR ARRAY OF DIMENSION LIWRK) THIS IS AN INTEGER WORK ARRAY. THE USER NEED NOT PLACE ANY VALUES IN IT, EXCEPT POSSIBLY CERTAIN OPTIONAL INFORMATION AS DESCRIBED BELOW.

    integer, intent(in) :: liwrk

    THIS IS THE DIMENSION OF IWORK IN THE DRIVER PROGRAM. IT MUST BE AT LEAST 7NUMGR + 7NPARM + 3. IF NOT, CONMAX WILL RETURN WITH THIS MINIMUM VALUE MULTIPLIED BY -1 AS A WARNING.

    real(kind=wp), intent(inout) :: work(Lwrk)

    (VECTOR ARRAY OF DIMENSION LWRK) THIS IS A FLOATING POINT WORK ARRAY. THE USER NEED NOT PLACE ANY VALUES IN IT, EXCEPT POSSIBLY CERTAIN OPTIONAL INFORMATION AS DESCRIBED BELOW.

    integer, intent(in) :: lwrk

    THIS IS THE DIMENSION OF WORK IN THE DRIVER PROGRAM. IT MUST BE AT LEAST 2NPARM2 + 4NUMGRNPARM + 11NUMGR + 27*NPARM + 13. IF NOT, CONMAX WILL RETURN WITH THIS MINIMUM VALUE MULTIPLIED BY -1 AS A WARNING.

    integer, intent(out) :: iter

    THIS IS THE NUMBER OF ITERATIONS PERFORMED BY CONMAX, INCLUDING THOSE USED IN ATTEMPTING TO GAIN FEASIBILITY, UNTIL EITHER IT CAN NO LONGER IMPROVE THE SITUATION OR THE ITERATION LIMIT IS REACHED. IF ITER=ITLIM IT IS POSSIBLE THAT THE PROGRAM COULD FURTHER REDUCE W IF RESTARTED (POSSIBLY WITH THE NEW PARAMETERS).

    Read more…
    real(kind=wp), intent(inout) :: param(Nparm)

    (VECTOR ARRAY OF DIMENSION AT LEAST NPARM IN THE DRIVER PROGRAM) THE USER SHOULD PLACE AN INITIAL GUESS FOR THE PARAMETERS IN PARAM, AND ON OUTPUT PARAM WILL CONTAIN THE BEST PARAMETERS CONMAX HAS BEEN ABLE TO FIND. IF THE INITIAL PARAM IS NOT FEASIBLE THE PROGRAM WILL FIRST TRY TO FIND A FEASIBLE PARAM.

    real(kind=wp), intent(out) :: error(Numgr+3)

    (VECTOR ARRAY OF DIMENSION AT LEAST NUMGR + 3 IN THE DRIVER PROGRAM) FOR I=1,...,NUMGR, CONMAX WILL PLACE IN ERROR(I) THE ERROR IN CONSTRAINT I (DEFINED TO BE THE VALUE OF THE LEFT SIDE OF CONSTRAINT I, EXCEPT WITHOUT THE ABSOLUTE VALUE IN TYPE 2 CONSTRAINTS). FURTHER,

    Read more…

procedure, public :: muller

  • private subroutine muller(me, Ioptn, Nparm, Numgr, Dvec, Fun, Ifun, Pttbl, Iptb, Indm, Zwork, Tolcon, Iphse, Iwork, Liwrk, Work, Lwrk, Parwrk, Err1, p1, f1, Procor, Emin)

    In this subroutine we are given a base vector zwork, a direction vector dvec, a scalar procor with emin = f(procor) = (the maximum type -2 and -1 error with parameters zwork + procor*dvec) < -tolcon, and a scalar p1 with p1 < procor and f1 = f(p1) > tolcon. we do a revised mullers method approach (with a solution contained in a shrinking interval) to attempt to adjust procor so that -tolcon <= f(procor) <= tolcon, but if we are not successful we return with the leftmost procor found satisfying emin = f(procor) < -tolcon on the theory that overcorrection is better than no correction. note that when corrct calls this subroutine it will have lumped the type -1 constraints in with the type -2 constraints using jcntyp, which is carried through this subroutine into subroutine ercmp1 in iwork.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer, intent(in) :: Nparm
    integer, intent(in) :: Numgr
    real(kind=wp) :: Dvec(Nparm)
    real(kind=wp) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp) :: Zwork(Nparm)
    real(kind=wp) :: Tolcon
    integer :: Iphse
    integer :: Iwork(Liwrk)
    integer :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    real(kind=wp) :: Parwrk(Nparm)
    real(kind=wp) :: Err1(Numgr+3)
    real(kind=wp) :: p1
    real(kind=wp) :: f1
    real(kind=wp) :: Procor
    real(kind=wp) :: Emin

procedure, public :: searsl

  • private subroutine searsl(me, Ioptn, Numgr, Nparm, Prjlim, Tol1, x, Fun, Ifun, Pttbl, Iptb, Indm, Param, Error, Rchdwn, Mact, Iact, Iphse, Unit, Tolcon, Rchin, Itypm1, Itypm2, Iwork, Liwrk, Work, Lwrk, Err1, Parprj, Projct, Emin, Emin1, Parser, Nsrch)

    This subroutine uses a modified quadratic fitting process to search for the minimum of a function f. it requres an initial guess in projct, a tolerance tol1 on the search interval length, an upper bound prjlim on the minimizing point (which should be set very large if no upper bound is desired), and a way to compute f(x) for a given x. the subroutine will print a warning and return if it would need to compute f more than initlm times in the initialization or more than nadd additional times in the main part of the program. when the subroutine returns, it will have put the minimum location in projct, the minimum f value in emin, the f value for the initial projct in emin1, and the number of times it computed f in nsrch.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer :: Numgr
    integer :: Nparm
    real(kind=wp) :: Prjlim
    real(kind=wp) :: Tol1
    real(kind=wp), dimension(nparm + 1) :: x
    real(kind=wp), dimension(ifun) :: Fun
    integer :: Ifun
    real(kind=wp), dimension(iptb, indm) :: Pttbl
    integer :: Iptb
    integer :: Indm
    real(kind=wp), dimension(nparm) :: Param
    real(kind=wp), dimension(numgr + 3) :: Error
    real(kind=wp) :: Rchdwn
    integer :: Mact
    integer, dimension(numgr) :: Iact
    integer :: Iphse
    real(kind=wp) :: Unit
    real(kind=wp) :: Tolcon
    real(kind=wp) :: Rchin
    integer :: Itypm1
    integer :: Itypm2
    integer, dimension(liwrk) :: Iwork
    integer :: Liwrk
    real(kind=wp), dimension(lwrk) :: Work
    integer :: Lwrk
    real(kind=wp), dimension(numgr + 3) :: Err1
    real(kind=wp), dimension(nparm) :: Parprj
    real(kind=wp) :: Projct
    real(kind=wp) :: Emin
    real(kind=wp) :: Emin1
    real(kind=wp), dimension(nparm) :: Parser
    integer :: Nsrch

procedure(func), public, deferred :: fnset

  • subroutine func(me, Nparm, Numgr, Pttbl, Iptb, Indm, Param, Ipt, Indfn, Icntyp, Confun) Prototype

    Interface for the fnset function.

    The first eight variables in the calling sequence for fnset are for input to fnset, with the first five variables being exactly as the user set them in the driver program. if the ten thousands digit of ioptn was set to 0, fnset should be written to place the appropriate values in icntyp and confun using the parameters in param, as follows:

    • icntyp(ipt) = the type of the ipt(th) constraint (i.e. 2, 1, -1, or -2), or the user can set icntyp(ipt)=0 as a signal to ignore constraint ipt.

    • confun(ipt,1) = the appropriate value as discussed above. (this can be left undefined if icntyp(ipt)=0.)

    if indfn=1 (which is the only possibility other than indfn=0) then in addition to the above, for j=1,...,nparm, fnset should compute

    confun(ipt,j+1) = the value of the partial derivative with respect to param(j) of the function whose value was computed in confun(ipt,1) (unless icntyp(ipt)=0, in which case these values need not be computed).

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer, intent(in) :: Nparm
    integer, intent(in) :: Numgr
    real(kind=wp), intent(in), dimension(Iptb, Indm) :: Pttbl
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp), intent(in), dimension(Nparm) :: Param
    integer, intent(in) :: Ipt
    integer, intent(in) :: Indfn
    integer, intent(out), dimension(Numgr) :: Icntyp
    real(kind=wp), intent(out), dimension(Numgr,Nparm+1) :: Confun

procedure, private :: ercmp1

  • private subroutine ercmp1(me, Ioptn, Nparm, Numgr, Fun, Ifun, Pttbl, Iptb, Indm, Param, Icnuse, Iphse, Iwork, Liwrk, Confun, Icntyp, Ipmax, Ismax, Error)

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer, intent(in) :: Ioptn
    integer, intent(in) :: Nparm
    integer, intent(in) :: Numgr
    real(kind=wp), intent(in) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp), intent(in) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp), intent(in) :: Param(Nparm)
    integer, intent(in) :: Icnuse
    integer, intent(in) :: Iphse
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Confun(Numgr,Nparm+1)
    integer :: Icntyp(Numgr)
    integer, intent(out) :: Ipmax
    integer, intent(out) :: Ismax
    real(kind=wp) :: Error(Numgr+3)

procedure, private :: rkcon

  • private subroutine rkcon(me, Ioptn, Nparm, Numgr, Fun, Ifun, Pttbl, Iptb, Indm, Tolcon, Rchin, Iter, Irk, Ityp2, Ityp1, Itypm1, Itypm2, Icntyp, Projct, Rchdwn, Nstep, Iphse, Enchg, Enc1, Pmat, Funtbl, Iwork, Liwrk, Work, Lwrk, Iact, Actdif, Parprj, Parser, Xrk, Err1, Confun, Isucc, Param, Error)

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer, intent(in) :: Nparm
    integer, intent(in) :: Numgr
    real(kind=wp) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer :: Indm
    real(kind=wp) :: Tolcon
    real(kind=wp) :: Rchin
    integer :: Iter
    integer :: Irk
    integer :: Ityp2
    integer :: Ityp1
    integer :: Itypm1
    integer :: Itypm2
    integer :: Icntyp(Numgr)
    real(kind=wp) :: Projct
    real(kind=wp) :: Rchdwn
    integer :: Nstep
    integer :: Iphse
    real(kind=wp) :: Enchg
    real(kind=wp) :: Enc1
    real(kind=wp) :: Pmat(Nparm+1,Numgr)
    real(kind=wp) :: Funtbl(Numgr,Nparm+1)
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    integer :: Iact(Numgr)
    real(kind=wp) :: Actdif(Numgr)
    real(kind=wp) :: Parprj(Nparm)
    real(kind=wp) :: Parser(Nparm)
    real(kind=wp) :: Xrk(Nparm+1)
    real(kind=wp) :: Err1(Numgr+3)
    real(kind=wp) :: Confun(Numgr,Nparm+1)
    integer :: Isucc
    real(kind=wp) :: Param(Nparm)
    real(kind=wp) :: Error(Numgr+3)

procedure, private :: slpcon

  • private subroutine slpcon(me, Ioptn, Nparm, Numgr, Fun, Ifun, Pttbl, Iptb, Indm, Tolcon, Rchin, Irk, Itypm1, Itypm2, Icntyp, Rchdwn, Numlim, Itersl, Prjslp, Funtbl, Iyrct, x, Mact1, Iact1, Jcntyp, Iphse, Enchg, Iwork, Liwrk, Work, Lwrk, Parser, Isucc, Param, Error)

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer, intent(in) :: Nparm
    integer, intent(in) :: Numgr
    real(kind=wp) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp) :: Tolcon
    real(kind=wp) :: Rchin
    integer :: Irk
    integer :: Itypm1
    integer :: Itypm2
    integer :: Icntyp(Numgr)
    real(kind=wp) :: Rchdwn
    integer :: Numlim
    integer :: Itersl
    real(kind=wp) :: Prjslp
    real(kind=wp) :: Funtbl(Numgr,Nparm+1)
    integer :: Iyrct(Numgr+2*Nparm)
    real(kind=wp) :: x(Nparm+1)
    integer :: Mact1
    integer :: Iact1(Numgr)
    integer :: Jcntyp(Numgr)
    integer :: Iphse
    real(kind=wp) :: Enchg
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    real(kind=wp) :: Parser(Nparm)
    integer :: Isucc
    real(kind=wp) :: Param(Nparm)
    real(kind=wp) :: Error(Numgr+3)

procedure, private :: corrct

  • private subroutine corrct(me, Ioptn, Nparm, Numgr, Fun, Ifun, Pttbl, Iptb, Indm, Icntyp, Unit, Tolcon, Rchin, Error, Mact, Iact, Projct, Iphse, Iwork, Liwrk, Work, Lwrk, Parwrk, Err1, Dvec, Pmat, Confun, Zwork, Jcntyp, Parprj, Icorct)

    This subroutine determines whether parprj violates any type -2 or type -1 (i.e. standard) constraints by more than tolcon, and if so it attempts to correct back to the feasible region. if it is successful it sets icorct=0 and replaces parprj by the corrected vector. if it is not successful it sets icorct=1 and leaves parprj unchanged. if no correction was needed it sets icorct=-1 and leaves parprj unchanged.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer, intent(in) :: Nparm
    integer, intent(in) :: Numgr
    real(kind=wp) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer :: Indm
    integer :: Icntyp(Numgr)
    real(kind=wp) :: Unit
    real(kind=wp) :: Tolcon
    real(kind=wp) :: Rchin
    real(kind=wp) :: Error(Numgr+3)
    integer :: Mact
    integer :: Iact(Numgr)
    real(kind=wp) :: Projct
    integer :: Iphse
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    real(kind=wp) :: Parwrk(Nparm)
    real(kind=wp) :: Err1(Numgr+3)
    real(kind=wp) :: Dvec(Nparm)
    real(kind=wp) :: Pmat(Nparm+1,Numgr)
    real(kind=wp) :: Confun(Numgr,Nparm+1)
    real(kind=wp) :: Zwork(Nparm)
    integer :: Jcntyp(Numgr)
    real(kind=wp) :: Parprj(Nparm)
    integer :: Icorct

procedure, private :: rkpar

  • private subroutine rkpar(me, Ioptn, Numgr, Nparm, Icntyp, Mactrk, Iact, Actdif, Projct, Param, Fun, Ifun, Pttbl, Iptb, Indm, Vder, Pmat, Ncor, s, Itypm1, Itypm2, Unit, Tolcon, Rchin, Nstep, Error, Iphse, Iwork, Liwrk, Work, Lwrk, Confun, Vdern, Vders, Wvec, Parprj, Ifrkpr)

    This subroutine computes a parameter vector parprj using fourth order runge kutta with h=-projct. h is negative since we want to approximate the parameters resulting from decreasing w by abs(h). if we do nstep steps then h=-projct/nstep.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer, intent(in) :: Numgr
    integer, intent(in) :: Nparm
    integer :: Icntyp(Numgr)
    integer :: Mactrk
    integer :: Iact(Numgr)
    real(kind=wp) :: Actdif(Numgr)
    real(kind=wp) :: Projct
    real(kind=wp) :: Param(Nparm)
    real(kind=wp) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp) :: Vder(Nparm)
    real(kind=wp) :: Pmat(Nparm+1,Numgr)
    integer :: Ncor
    real(kind=wp) :: s
    integer :: Itypm1
    integer :: Itypm2
    real(kind=wp) :: Unit
    real(kind=wp) :: Tolcon
    real(kind=wp) :: Rchin
    integer :: Nstep
    real(kind=wp) :: Error(Numgr+3)
    integer :: Iphse
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    real(kind=wp) :: Confun(Numgr,Nparm+1)
    real(kind=wp) :: Vdern(Nparm)
    real(kind=wp) :: Vders(Nparm)
    real(kind=wp) :: Wvec(Nparm)
    real(kind=wp) :: Parprj(Nparm)
    integer :: Ifrkpr

procedure, private :: searcr

  • private subroutine searcr(me, Ioptn, Nparm, Numgr, Dvec, Fun, Ifun, Pttbl, Iptb, Indm, Zwork, Tolcon, Iphse, Iwork, Liwrk, Work, Lwrk, Parwrk, Err1, p1, f1, Procor, Emin, Isrcr)

    This subroutine uses a modified quadratic fitting process to search for a projection factor procor for which the maximum of the left sides of the type -2 and -1 constraints evaluated at zwork + procor*dvec is <= tolcon. note that when corrct calls this subroutine it will have lumped the type -1 constraints in with the type -2 constraints using jcntyp, which is carried through this subroutine into subroutine ercmp1 in iwork. if searcr is able to force this maximum <= tolcon it will return with isrcr=0, with the minimum value found for the maximum in emin, with the corresponding projection factor in procor, with the number of times the maximum was computed in nsrch, and with the closest point found to the left with the maximum > tolcon in (p1,f1). the subroutine will begin by computing the maxima for procor = 1.0, 0.5, and 2.0, and if none of these maxima is <= tolcon and it is not the case that the maximum at 1.0 is <= the other two maxima the subroutine will return with the warning isrcr=1. the subroutine will also return with isrcr=1 if it would need to compute f more than limscr times, or the search interval length drops below tol1, or the quadratic fit becomes too flat. even in the event of a return with isrcr=1, emin, procor, and nsrch will be as above.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer, intent(in) :: Nparm
    integer :: Numgr
    real(kind=wp) :: Dvec(Nparm)
    real(kind=wp) :: Fun(Ifun)
    integer, intent(in) :: Ifun
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp) :: Zwork(Nparm)
    real(kind=wp) :: Tolcon
    integer :: Iphse
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    real(kind=wp) :: Parwrk(Nparm)
    real(kind=wp) :: Err1(Numgr+3)
    real(kind=wp) :: p1
    real(kind=wp) :: f1
    real(kind=wp) :: Procor
    real(kind=wp) :: Emin
    integer :: Isrcr

procedure, private :: derst

  • private subroutine derst(me, Ioptn, Nparm, Numgr, Pttbl, Iptb, Indm, Param, Ipt, Param1, v, Kcntyp, Confun)

    This subroutine uses fnset to compute confun(i,1) and the partial derivatives of the function whose value is in confun(i,1) for certain value(s) of i. note that we do not want the icntyp computed by fnset to override the icntyp (or jcntyp) carried into this subroutine in icntyp, so we use kcntyp when we call fnset. (the icntyp computed by fnset was stored earlier through a call to ercmp1 from conmax.)

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer, intent(in) :: Ioptn
    integer :: Nparm
    integer :: Numgr
    real(kind=wp), dimension(Iptb, Indm) :: Pttbl
    integer :: Iptb
    integer :: Indm
    real(kind=wp), dimension(Nparm) :: Param
    integer :: Ipt
    real(kind=wp), dimension(Nparm) :: Param1
    real(kind=wp), dimension(Numgr + 2*Nparm + 1, Nparm + 2) :: v
    integer, dimension(Numgr) :: Kcntyp
    real(kind=wp), dimension(Numgr, Nparm + 1) :: Confun

procedure, private :: setu1

  • private subroutine setu1(me, Ioptn, Numgr, Nparm, Numin, Rchin, Pttbl, Iptb, Indm, Fun, Ifun, Funtbl, Cofbnd, Param, Icntyp, Rchdwn, Error, Mact1, Iact1, Bndlgt, Iyrct, Iphse, Iwork, Liwrk, Work, Lwrk, Confun, Iact, v, m)

    This subroutine sets up v for slnpro to solve a modified linearized (about the old parameters in param) version of our problem.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer :: Ioptn
    integer :: Numgr
    integer :: Nparm
    integer :: Numin
    real(kind=wp) :: Rchin
    real(kind=wp), dimension(iptb, indm) :: Pttbl
    integer :: Iptb
    integer :: Indm
    real(kind=wp), dimension(ifun) :: Fun
    integer :: Ifun
    real(kind=wp), dimension(numgr, nparm + 1) :: Funtbl
    real(kind=wp), dimension(nparm) :: Cofbnd
    real(kind=wp), dimension(nparm) :: Param
    integer, dimension(numgr) :: Icntyp
    real(kind=wp) :: Rchdwn
    real(kind=wp), dimension(numgr + 3) :: Error
    integer :: Mact1
    integer, dimension(numgr) :: Iact1
    real(kind=wp) :: Bndlgt
    integer, dimension(numgr + 2*nparm) :: Iyrct
    integer :: Iphse
    integer, dimension(liwrk) :: Iwork
    integer :: Liwrk
    real(kind=wp), dimension(lwrk) :: Work
    integer :: Lwrk
    real(kind=wp), dimension(numgr, nparm + 1) :: Confun
    integer, dimension(numgr) :: Iact
    real(kind=wp), dimension(numgr + 2*nparm + 1, nparm + 2) :: v
    integer :: m

procedure, private :: pmtst

  • private subroutine pmtst(me, Ioptn, Numgr, Nparm, Param, Icntyp, Mactrk, Iact, Pttbl, Iptb, Indm, Actdif, Iphse, Iwork, Liwrk, Work, Lwrk, Confun, Pmat)

    This subroutine sets up the (nparm+1) by mactrk matrix pmat. for 1 <= j <= mactrk, the top nparm elements of column j of pmat will contain the negative of the gradient of active constraint j (if constraint j is of type 2, i.e. of the form abs(f(x) - f(parwrk,x)) <= w, the left side will be treated as f(x) - f(parwrk,x) if this quantity is nonnegative and will be treated as f(parwrk,x) - f(x) otherwise). the (nparm+1)st row of pmat will contain actdif, the right side of the inequalities gradient.vector >= actdif.

    Arguments

    Type IntentOptional Attributes Name
    class(conmax_solver), intent(inout) :: me
    integer, intent(in) :: Ioptn
    integer, intent(in) :: Numgr
    integer, intent(in) :: Nparm
    real(kind=wp) :: Param(Nparm)
    integer :: Icntyp(Numgr)
    integer, intent(in) :: Mactrk
    integer :: Iact(Numgr)
    real(kind=wp) :: Pttbl(Iptb,Indm)
    integer, intent(in) :: Iptb
    integer, intent(in) :: Indm
    real(kind=wp), intent(in) :: Actdif(Numgr)
    integer, intent(in) :: Iphse
    integer :: Iwork(Liwrk)
    integer, intent(in) :: Liwrk
    real(kind=wp) :: Work(Lwrk)
    integer, intent(in) :: Lwrk
    real(kind=wp) :: Confun(Numgr,Nparm+1)
    real(kind=wp) :: Pmat(Nparm+1,Numgr)

Source Code

    type, abstract, public :: conmax_solver
        !! main CONMAX solver class. This class must be
        !! extended to define the users's `fnset` function.
        private
    contains
        private
        procedure, public :: solve => conmax  !! main solver routine
        procedure, public :: muller
        procedure, public :: searsl
        procedure(func), deferred, public :: fnset
        procedure :: ercmp1
        procedure :: rkcon
        procedure :: slpcon
        procedure :: corrct
        procedure :: rkpar
        procedure :: searcr
        procedure :: derst
        procedure :: setu1
        procedure :: pmtst
    end type conmax_solver