NAG Library Manual, Mark 29.3
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
!   E05SBF Example Program Text
!   Mark 29.3 Release. NAG Copyright 2023.

    Module e05sbfe_mod

!     E05SBF Example Program Module:
!            Parameters and User-defined Routines

!     .. Use Statements ..
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: confun_non_linear, display_option,   &
                                          display_result, monmod,              &
                                          objfun_schwefel
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter, Public :: f_target_c =                    &
                                          -731.70709230672696_nag_wp
      Real (Kind=nag_wp), Parameter, Public :: zero = 0.0_nag_wp
      Real (Kind=nag_wp), Parameter    :: f_target_u =                         &
                                          -837.9657745448674_nag_wp
      Real (Kind=nag_wp), Parameter    :: x_target = -420.9687463599820_nag_wp
      Integer, Parameter               :: detail_level = 0, report_freq = 100
      Integer, Parameter, Public       :: liopts = 100, liuser = 1,            &
                                          lopts = 100, lruser = 1, ncon = 3,   &
                                          ndim = 2, nout = 6
      Real (Kind=nag_wp), Parameter    :: c_scale(ncon) = (/2490.0_nag_wp,     &
                                          750000.0_nag_wp,0.1_nag_wp/)
      Real (Kind=nag_wp), Parameter    :: c_target_c(ncon) = 0._nag_wp
      Real (Kind=nag_wp), Parameter    :: c_target_u(ncon) = (/zero,           &
                                          31644.05623568455_nag_wp,            &
                                          0.07574889943398055_nag_wp/)
      Real (Kind=nag_wp), Parameter    :: x_target_c(ndim) = (/                &
                                          -394.1470221120988_nag_wp,           &
                                          -433.48214189947606_nag_wp/)
      Real (Kind=nag_wp), Parameter    :: x_target_u(ndim) = (/x_target,       &
                                          x_target/)
    Contains
      Subroutine objfun_schwefel(mode,ndim,x,objf,vecout,nstate,iuser,ruser)
!       Objfun routine for the Schwefel function for E05SBF.

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: objf
        Integer, Intent (Inout)        :: mode
        Integer, Intent (In)           :: ndim, nstate
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*), vecout(ndim)
        Real (Kind=nag_wp), Intent (In) :: x(ndim)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Logical                        :: evalobjf, evalobjg
!       .. Intrinsic Procedures ..
        Intrinsic                      :: abs, cos, sin, sqrt, sum
!       .. Executable Statements ..
!       Test NSTATE to indicate what stage of computation has been reached.
        Select Case (nstate)
        Case (2)
!         OBJFUN is called for the very first time.
        Case (1)
!         OBJFUN is called on entry to a NAG local minimizer.
        Case (0)
!         This will be the normal value of NSTATE.
        End Select

!       Test MODE to determine whether to calculate OBJF and/or OBJGRD.
        evalobjf = .False.
        evalobjg = .False.
        Select Case (mode)
        Case (0,5)
!         Only the value of the objective function is needed.
          evalobjf = .True.
        Case (1,6)
!         Only the values of the NDIM gradients are required.
          evalobjg = .True.
        Case (2,7)
!         Both the objective function and the NDIM gradients are required.
          evalobjf = .True.
          evalobjg = .True.
        End Select

        If (evalobjf) Then
!         Evaluate the objective function.
          objf = sum(x(1:ndim)*sin(sqrt(abs(x(1:ndim)))))
        End If

        If (evalobjg) Then
!         Calculate the gradient of the objective function.
          vecout = sqrt(abs(x))
          vecout = sin(vecout) + 0.5E0_nag_wp*vecout*cos(vecout)
        End If

        Return

      End Subroutine objfun_schwefel
      Subroutine confun_non_linear(mode,ncon,ndim,ldcj,needc,x,c,cjac,nstate,  &
        iuser,ruser)
!       Subroutine used to supply constraints

!       .. Scalar Arguments ..
        Integer, Intent (In)           :: ldcj, ncon, ndim, nstate
        Integer, Intent (Inout)        :: mode
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: c(ncon)
        Real (Kind=nag_wp), Intent (Inout) :: cjac(ldcj,ndim), ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(ndim)
        Integer, Intent (Inout)        :: iuser(*)
        Integer, Intent (In)           :: needc(ncon)
!       .. Local Scalars ..
        Integer                        :: k
        Logical                        :: evalc, evalcjac
!       .. Intrinsic Procedures ..
        Intrinsic                      :: cos
!       .. Executable Statements ..
!       Test NSTATE to determine whether the local minimizer is being called
!       for the first time from a new start point
        If (nstate==1) Then
!         Set any constant elements of the Jacobian matrix.
          cjac(1,1) = 3.0_nag_wp
          cjac(1,2) = -2.0_nag_wp
        End If

!       MODE: are constraints, derivatives, or both are required?
        evalc = mode == 0 .Or. mode == 2
        evalcjac = mode == 1 .Or. mode == 2

loop_constraints: Do k = 1, ncon
!         Only those for which needc is nonzero need be set.
          If (needc(k)<=0) Then
            Cycle loop_constraints
          End If

          If (evalc) Then
!           Constraint values are required.
            Select Case (k)
            Case (1)
              c(k) = 3.0_nag_wp*x(1) - 2.0_nag_wp*x(2)
            Case (2)
              c(k) = x(1)**2 - x(2)**2 + 3.0_nag_wp*x(1)*x(2)
            Case (3)
              c(k) = cos((x(1)/200.0_nag_wp)**2+(x(2)/100.0_nag_wp))
            Case Default
!             This constraint is not coded (there are only three).
!             Terminate.
              mode = -1
              Exit loop_constraints
            End Select
          End If

          If (evalcjac) Then
!           Constraint derivatives (CJAC) are required.
            Select Case (k)
            Case (1)
!             Constant derivatives set when NSTATE=1 remain throughout
!             the local minimization.
            Case (2)
!             If the constraint derivatives are known and are readily
!             calculated, populate CJAC when required.
              cjac(k,1) = 2.0_nag_wp*x(1) + 3.0_nag_wp*x(2)
              cjac(k,2) = -2.0_nag_wp*x(2) + 3.0_nag_wp*x(1)
            Case Default
!             Any elements of CJAC left unaltered will be approximated
!             using finite differences when required.
            End Select
          End If

        End Do loop_constraints

        Return

      End Subroutine confun_non_linear
      Subroutine monmod(ndim,ncon,npar,x,xb,fb,cb,xbest,fbest,cbest,itt,iuser, &
        ruser,inform)

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: fb
        Integer, Intent (Inout)        :: inform
        Integer, Intent (In)           :: ncon, ndim, npar
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: cb(ncon), cbest(ncon,npar),         &
                                          fbest(npar), xb(ndim),               &
                                          xbest(ndim,npar)
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*), x(ndim,npar)
        Integer, Intent (In)           :: itt(7)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Integer                        :: indent, j
!       .. Intrinsic Procedures ..
        Intrinsic                      :: modulo, repeat
!       .. Executable Statements ..
        If (detail_level>=2) Then
!         Report on the first iteration, and every report_freq iterations.
          If (itt(1)==1 .Or. modulo(itt(1),report_freq)==0) Then
            Write (nout,*) '* Locations of particles'
            indent = 2
            Do j = 1, npar
              Write (nout,99999) repeat(' ',indent), j
              Write (nout,99998) repeat(' ',indent), x(1:ndim,j)
            End Do
            Write (nout,*) '* Cognitive memory'
            Do j = 1, npar
              Write (nout,99999) repeat(' ',indent), j
              Write (nout,*) repeat(' ',indent*2), '* Best position'
              Write (nout,99998) repeat(' ',indent*2), xbest(1:ndim,j)
              Write (nout,*) repeat(' ',indent*2),                             &
                '* Function value at best position'
              Write (nout,99997) repeat(' ',indent*2), fbest(j)
              Write (nout,*) repeat(' ',indent*2),                             &
                '* Best constraint violations'
              Write (nout,99998) repeat(' ',indent*2), cbest(1:ncon,j)
            End Do
            Write (nout,*) '* Current global optimum candidate'
            Write (nout,99998) repeat(' ',indent), xb(1:ndim)
            Write (nout,*) '* Current global optimum value'
            Write (nout,99997) repeat(' ',indent), fb
            Write (nout,*) '* Constraint violations of candidate'
            Write (nout,99998) repeat(' ',indent), cb(1:ncon)
          End If
        End If

!       If required set INFORM<0 to force exit
        inform = 0

        Return
99999   Format (1X,A,'* Particle ',I3)
99998   Format (1X,A,(6F13.5))
99997   Format (1X,A,F13.5)
      End Subroutine monmod
      Subroutine display_option(optstr,optype,ivalue,rvalue,cvalue)
!       Subroutine to query optype and print the appropriate option values

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: rvalue
        Integer, Intent (In)           :: ivalue, optype
        Character (*), Intent (In)     :: cvalue, optstr
!       .. Executable Statements ..
        Select Case (optype)
        Case (1)
          Write (nout,99999) optstr, ivalue
        Case (2)
          Write (nout,99998) optstr, rvalue
        Case (3)
          Write (nout,99997) optstr, cvalue
        Case (4)
          Write (nout,99996) optstr, ivalue, cvalue
        Case (5)
          Write (nout,99995) optstr, rvalue, cvalue
        End Select

        Flush (nout)

        Return
99999   Format (3X,A39,' : ',I13)
99998   Format (3X,A39,' : ',F13.4)
99997   Format (3X,A39,' : ',16X,A16)
99996   Format (3X,A39,' : ',I13,3X,A16)
99995   Format (3X,A39,' : ',F13.4,3X,A16)
      End Subroutine display_option

      Subroutine display_result(ndim,ncon,xb,fb,cb,itt,inform)
!       Display final results in comparison to known global optimum.

!       .. Use Statements ..
        Use nag_library, Only: x04cbf
!       .. Parameters ..
        Integer, Parameter             :: indent = 1, ncols = 79
        Character (11), Parameter      :: clabs(1:6) = (/'x_target_u ',        &
                                          'x_target_c ','xb         ',         &
                                          'c_target_u ','c_target_c ',         &
                                          'cb         '/)
        Character (1), Parameter       :: diag = 'D', labcol = 'C',            &
                                          labrow = 'I', matrix = 'G'
        Character (5), Parameter       :: fmtc = 'f12.5', fmtx = 'f12.2'
!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: fb
        Integer, Intent (In)           :: inform, ncon, ndim
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: cb(ncon), xb(ndim)
        Integer, Intent (In)           :: itt(7)
!       .. Local Scalars ..
        Integer                        :: ifail, ldcom
        Character (ncols)              :: titlec, titlex
!       .. Local Arrays ..
        Real (Kind=nag_wp), Allocatable :: ccom(:,:), xcom(:,:)
!       .. Executable Statements ..
!       Display final counters.
        Write (nout,*) ' Algorithm Statistics'
        Write (nout,*) ' --------------------'
        Write (nout,99994) 'Total complete iterations               ', itt(1)
        Write (nout,99994) 'Complete iterations since improvement   ', itt(2)
        Write (nout,99994) 'Total particles converged to xb         ', itt(3)
        Write (nout,99994) 'Total improvements to global optimum    ', itt(4)
        Write (nout,99994) 'Total function evaluations              ', itt(5)
        Write (nout,99994) 'Total particles re-initialized          ', itt(6)
        Write (nout,99994) 'Total constraints violated              ', itt(7)

!       Display why finalization occurred.
        Write (nout,*)
        Select Case (inform)
        Case (1)
          Write (nout,99999) 'Target value achieved'
        Case (2)
          Write (nout,99999) 'Minimum swarm standard deviation obtained'
        Case (3)
          Write (nout,99999) 'Sufficient particles converged'
        Case (4)
          Write (nout,99999) 'No improvement in preset iteration limit'
        Case (5)
          Write (nout,99999) 'Maximum complete iterations attained'
        Case (6)
          Write (nout,99999) 'Maximum function evaluations exceeded'
        Case (7)
          Write (nout,99999) 'Constrained point located'
        Case (:-1)
          Write (nout,99998) inform
          Go To 100
        End Select

!       Display final objective value and location.
        Write (nout,*)
        Write (nout,99997) f_target_u
        Write (nout,99996) f_target_c
        Write (nout,99995) fb

        ldcom = ndim
        Allocate (xcom(ldcom,3))
        xcom(1:ndim,1) = x_target_u(1:ndim)
        xcom(1:ndim,2) = x_target_c(1:ndim)
        xcom(1:ndim,3) = xb(1:ndim)

        Write (nout,*)
        Flush (nout)
        titlex = 'Comparison between known and achieved optima.'
        ifail = 0
        Call x04cbf(matrix,diag,ndim,3,xcom,ldcom,fmtx,titlex,labrow,clabs,    &
          labcol,clabs,ncols,indent,ifail)

        Deallocate (xcom)

        If (ncon>0) Then
          ldcom = ncon
          Allocate (ccom(ldcom,3))
          ccom(1:ncon,1) = c_target_u(1:ncon)/c_scale(1:ncon)
          ccom(1:ncon,2) = c_target_c(1:ncon)/c_scale(1:ncon)
          ccom(1:ncon,3) = cb(1:ncon)/c_scale(1:ncon)

          Write (nout,*)
          Flush (nout)
          titlec = 'Comparison between scaled constraint violations.'
          ifail = 0
          Call x04cbf(matrix,diag,ncon,3,ccom,ldcom,fmtc,titlec,labrow,clabs,  &
            labcol,clabs(4:6),ncols,indent,ifail)

          Deallocate (ccom)
        End If

100     Continue

        Write (nout,*)

        Return
99999   Format (2X,'Solution Status : ',A38)
99998   Format ('  User termination case                    : ',I13)
99997   Format ('  Known unconstrained objective minimum    : ',F13.3)
99996   Format ('  Best Known constrained objective minimum : ',F13.3)
99995   Format ('  Achieved objective value                 : ',F13.3)
99994   Format (2X,A40,' :',I13)
      End Subroutine display_result
    End Module e05sbfe_mod
    Program e05sbfe
!     E05SBF Example Main Program

!     This example program demonstrates how to use E05SBF in standard
!       execution, and with E04UCF as a coupled local minimizer.
!     The non-default option 'REPEATABILITY ON' is used here, giving
!       repeatable results.

!     .. Use Statements ..
      Use e05sbfe_mod, Only: confun_non_linear, display_option,                &
                             display_result, f_target_c, liopts, liuser,       &
                             lopts, lruser, monmod, ncon, ndim, nout,          &
                             objfun_schwefel, zero
      Use nag_library, Only: e05sbf, e05zkf, e05zlf, nag_wp, x06acf
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: fb, rvalue
      Integer                          :: ifail, inform, ivalue, npar, optype
      Character (16)                   :: cvalue
      Character (80)                   :: optstr
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: bl(ndim+ncon), bu(ndim+ncon),        &
                                          cb(ncon), opts(lopts),               &
                                          ruser(lruser), xb(ndim)
      Real (Kind=nag_wp), Allocatable  :: cbest(:,:), fbest(:,:), xbest(:,:)
      Integer                          :: iopts(liopts), itt(7), iuser(liuser)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
!     Print advisory information.
      Write (nout,*) 'E05SBF Example Program Results'
      Write (nout,*)
      Write (nout,*) 'Minimization of the Schwefel function.'
      Write (nout,*) 'Subject to one linear and two nonlinear constraints.'
      Write (nout,*)

!     Determine the number of particles to be used in the simulation.
      npar = 10*max(x06acf(),ndim)

      Allocate (xbest(ndim,npar),cbest(ncon,npar),fbest(ndim,npar))

      xbest = zero
      fbest = zero
      cbest = zero

!     Set problem specific values.
!     Set box bounds.
      bl(1:ndim) = -500.0_nag_wp
      bu(1:ndim) = 500.0_nag_wp
!     Set constraint bounds.
      bl((ndim+1):(ndim+ncon)) = (/-1.0E6_nag_wp,-1.0_nag_wp,-0.9_nag_wp/)
      bu((ndim+1):(ndim+ncon)) = (/10.0_nag_wp,5.0E5_nag_wp,0.9_nag_wp/)

!     Initialize the option arrays for E05SBF.
      ifail = 0
      Call e05zkf('Initialize = E05SBF',iopts,liopts,opts,lopts,ifail)

!     Set the option SMP Callback Thread Safe to indicate the callback functions
!     are indeed threadsafe.  This must be done if using multiple threads.

      ifail = 0
      Call e05zkf('SMP Callback Thread Safe = Yes',iopts,liopts,opts,lopts,    &
        ifail)

!     Query some default option values.
      Write (nout,*) '  Default Option Queries:'
      Write (nout,*)
      ivalue = 0
      rvalue = 0.0_nag_wp
      ifail = 0
      optstr = 'Constraint Norm'
      Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail)
      Call display_option(optstr,optype,ivalue,rvalue,cvalue)

      ifail = 0
      optstr = 'Maximum Iterations Completed'
      Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail)
      Call display_option(optstr,optype,ivalue,rvalue,cvalue)

      ifail = 0
      optstr = 'Distance Tolerance'
      Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail)
      Call display_option(optstr,optype,ivalue,rvalue,cvalue)

!     ------------------------------------------------------------------
      Write (nout,*)
      Write (nout,*) '1. Solution without using coupled local minimizer'
      Write (nout,*)
!     Set various options to non-default values if required.
      ifail = 0
      Write (optstr,99999) 'Distance Tolerance', rvalue*0.1_nag_wp
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Write (optstr,99999) 'Constraint Tolerance', 1.0E-4_nag_wp
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Call e05zkf('Constraint Norm = Euclidean',iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Call e05zkf('Repeatability = On',iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Write (optstr,99999) 'Target Objective Value', f_target_c
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Write (optstr,99999) 'Target Objective Tolerance', 1.0E-4_nag_wp
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)

!     Call E05SBF to search for the global optimum.
!     Non-zero IFAIL expected on exit here, so use IFAIL=1 (quiet) on entry.
      ifail = 1
      Call e05sbf(ndim,ncon,npar,xb,fb,cb,bl,bu,xbest,fbest,cbest,             &
        objfun_schwefel,confun_non_linear,monmod,iopts,opts,iuser,ruser,itt,   &
        inform,ifail)

!     It is essential to test IFAIL on exit.
      Select Case (ifail)
      Case (0,1)
!       No errors, best found optimum at xb returned in fb.
        Call display_result(ndim,ncon,xb,fb,cb,itt,inform)
      Case (3)
!       Exit flag set in OBJFUN, CONFUN or MONMOD and returned in INFORM.
        Call display_result(ndim,ncon,xb,fb,cb,itt,inform)
      Case Default
!       An error was detected. Print message since IFAIL=1 on entry.
        Write (nout,99998) '** E05SBF returned with an error, IFAIL = ', ifail
      End Select

!     ------------------------------------------------------------------
      Write (nout,*) '2. Solution using coupled local minimizer E04UCF'
      Write (nout,*)

!     Set the local minimizer to be E04UCF and set corresponding options.
      ifail = 0
      Call e05zkf('Local Minimizer = E04UCF',iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Call e05zkf('Local Interior Major Iterations = 15',iopts,liopts,opts,    &
        lopts,ifail)
      ifail = 0
      Call e05zkf('Local Interior Minor Iterations = 5',iopts,liopts,opts,     &
        lopts,ifail)
      ifail = 0
      Call e05zkf('Local Exterior Major Iterations = 50',iopts,liopts,opts,    &
        lopts,ifail)
      ifail = 0
      Call e05zkf('Local Exterior Minor Iterations = 15',iopts,liopts,opts,    &
        lopts,ifail)

!     Query the option Distance Tolerance
      ifail = 0
      optstr = 'Distance Tolerance'
      Call e05zlf(optstr,ivalue,rvalue,cvalue,optype,iopts,opts,ifail)
!     Adjust Distance Tolerance dependent upon its current value
      Write (optstr,99999) 'Distance Tolerance', rvalue*10.0_nag_wp
      ifail = 0
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Write (optstr,99999) 'Local Interior Tolerance', rvalue
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)
      ifail = 0
      Write (optstr,99999) 'Local Exterior Tolerance', rvalue*1.0E-4_nag_wp
      Call e05zkf(optstr,iopts,liopts,opts,lopts,ifail)

!     Call E05SBF to search for the global optimum.
      ifail = 1
      Call e05sbf(ndim,ncon,npar,xb,fb,cb,bl,bu,xbest,fbest,cbest,             &
        objfun_schwefel,confun_non_linear,monmod,iopts,opts,iuser,ruser,itt,   &
        inform,ifail)

!     It is essential to test IFAIL on exit.
      Select Case (ifail)
      Case (0,1)
!       E05SBF encountered no errors during operation,
!       and will have returned the best found optimum.
        Call display_result(ndim,ncon,xb,fb,cb,itt,inform)
      Case (3)
!       Exit flag set in OBJFUN, CONFUN or MONMOD and returned in INFORM.
        Call display_result(ndim,ncon,xb,fb,cb,itt,inform)
      Case Default
!       An error was detected. Print message since IFAIL=1 on entry.
        Write (nout,99998) '** E05SBF returned with an error, IFAIL = ', ifail
      End Select

99999 Format (A,' = ',E32.16)
99998 Format (1X,A,I6)
    End Program e05sbfe