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

NAG FL Interface Introduction
Example description
!   E04KDF Example Program Text
!   Mark 28.5 Release. NAG Copyright 2022.
    Module e04kdfe_mod

!     E04KDF 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                           :: funct, monit
!     .. Parameters ..
      Integer, Parameter, Public       :: liw = 2, n = 4, nout = 6
      Integer, Parameter, Public       :: lh = n*(n-1)/2
      Integer, Parameter, Public       :: lw = 7*n + n*(n-1)/2
    Contains
      Subroutine funct(iflag,n,xc,fc,gc,iw,liw,w,lw)
!       Routine to evaluate objective function and its 1st derivatives.
!       A global variable could be updated here to count the number of
!       calls of FUNCT with IFLAG = 1 (since NF in MONIT only counts
!       calls with IFLAG = 2)

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: fc
        Integer, Intent (Inout)        :: iflag
        Integer, Intent (In)           :: liw, lw, n
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: gc(n)
        Real (Kind=nag_wp), Intent (Inout) :: w(lw)
        Real (Kind=nag_wp), Intent (In) :: xc(n)
        Integer, Intent (Inout)        :: iw(liw)
!       .. Executable Statements ..
        If (iflag/=1) Then
          fc = (xc(1)+10.0_nag_wp*xc(2))**2 + 5.0_nag_wp*(xc(3)-xc(4))**2 +    &
            (xc(2)-2.0_nag_wp*xc(3))**4 + 10.0_nag_wp*(xc(1)-xc(4))**4
        End If

        gc(1) = 2.0_nag_wp*(xc(1)+10.0_nag_wp*xc(2)) +                         &
          40.0_nag_wp*(xc(1)-xc(4))**3
        gc(2) = 20.0_nag_wp*(xc(1)+10.0_nag_wp*xc(2)) +                        &
          4.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3))**3
        gc(3) = 10.0_nag_wp*(xc(3)-xc(4)) - 8.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3) &
          )**3
        gc(4) = 10.0_nag_wp*(xc(4)-xc(3)) - 40.0_nag_wp*(xc(1)-xc(4))**3

        Return

      End Subroutine funct
      Subroutine monit(n,xc,fc,gc,istate,gpjnrm,cond,posdef,niter,nf,iw,liw,w, &
        lw)
!       Monitoring routine

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (In) :: cond, fc, gpjnrm
        Integer, Intent (In)           :: liw, lw, n, nf, niter
        Logical, Intent (In)           :: posdef
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In) :: gc(n), xc(n)
        Real (Kind=nag_wp), Intent (Inout) :: w(lw)
        Integer, Intent (In)           :: istate(n)
        Integer, Intent (Inout)        :: iw(liw)
!       .. Local Scalars ..
        Integer                        :: isj, j
!       .. Executable Statements ..
        Write (nout,*)
        Write (nout,*) ' Itn     Fn evals              Fn value' //            &
          '            Norm of proj gradient'
        Write (nout,99999) niter, nf, fc, gpjnrm
        Write (nout,*)
        Write (nout,*)                                                         &
          ' J           X(J)                G(J)           Status'

        Do j = 1, n
          isj = istate(j)

          Select Case (isj)
          Case (1:)
            Write (nout,99998) j, xc(j), gc(j), '    Free'
          Case (-1)
            Write (nout,99998) j, xc(j), gc(j), '    Upper Bound'
          Case (-2)
            Write (nout,99998) j, xc(j), gc(j), '    Lower Bound'
          Case (-3)
            Write (nout,99998) j, xc(j), gc(j), '    Constant'
          End Select

        End Do

        If (cond/=0.0_nag_wp) Then

          If (cond>1.0E6_nag_wp) Then
            Write (nout,*)
            Write (nout,*)                                                     &
              'Estimated condition number of projected Hessian is more than ', &
              '1.0E+6'
          Else
            Write (nout,*)
            Write (nout,99997)                                                 &
              'Estimated condition number of projected Hessian = ', cond
          End If

          If (.Not. posdef) Then
            Write (nout,*)
            Write (nout,*) 'Projected Hessian matrix is not positive definite'
          End If

        End If

        Return

99999   Format (1X,I3,6X,I5,2(6X,1P,E20.4))
99998   Format (1X,I2,1X,1P,2E20.4,A)
99997   Format (1X,A,1P,E10.2)
      End Subroutine monit
    End Module e04kdfe_mod
    Program e04kdfe

!     E04KDF Example Main Program

!     .. Use Statements ..
      Use e04kdfe_mod, Only: funct, lh, liw, lw, monit, n, nout
      Use nag_library, Only: e04hcf, e04kdf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: delta, eta, f, stepmx, xtol
      Integer                          :: ibound, ifail, iprint, maxcal
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: bl(n), bu(n), g(n), hesd(n),         &
                                          hesl(lh), w(lw), x(n)
      Integer                          :: istate(n), iw(liw)
!     .. Executable Statements ..
      Write (nout,*) 'E04KDF Example Program Results'
      Flush (nout)

!     Check FUNCT by calling E04HCF at an arbitrary point. Since E04HCF
!     only checks the derivatives calculated when IFLAG = 2, a separate
!     program should be run before using E04HCF or E04KDF to check that
!     FUNCT gives the same values for the GC(J) when IFLAG is set to 1
!     as when IFLAG is set to 2.

      x(1:n) = (/1.46_nag_wp,-0.82_nag_wp,0.57_nag_wp,1.21_nag_wp/)

      ifail = 0
      Call e04hcf(n,funct,x,f,g,iw,liw,w,lw,ifail)

!     Continue setting parameters for E04KDF

!     Set IPRINT to 1 to obtain output from MONIT at each iteration
      iprint = -1

      maxcal = 50*n
      eta = 0.5_nag_wp

!     Set XTOL and DELTA to zero so that E04KDF will use the default
!     values

      xtol = 0.0_nag_wp
      delta = 0.0_nag_wp

!     We estimate that the minimum will be within 4 units of the
!     starting point

      stepmx = 4.0_nag_wp

      ibound = 0

!     X(3) is not bounded, so we set BL(3) to a large negative
!     number and BU(3) to a large positive number

      bl(1:n) = (/1.0_nag_wp,-2.0_nag_wp,-1.0E6_nag_wp,1.0_nag_wp/)
      bu(1:n) = (/3.0_nag_wp,0.0_nag_wp,1.0E6_nag_wp,3.0_nag_wp/)

!     Set up starting point

      x(1:n) = (/3.0_nag_wp,-1.0_nag_wp,0.0_nag_wp,1.0_nag_wp/)

      ifail = -1
      Call e04kdf(n,funct,monit,iprint,maxcal,eta,xtol,delta,stepmx,ibound,bl, &
        bu,x,hesl,lh,hesd,istate,f,g,iw,liw,w,lw,ifail)

      Select Case (ifail)
      Case (0,2:)
        Write (nout,*)
        Write (nout,99999) 'Function value on exit is ', f
        Write (nout,99999) 'at the point', x(1:n)
        Write (nout,*) 'The corresponding (machine dependent) gradient is'
        Write (nout,99998) g(1:n)
        Write (nout,99997) 'ISTATE contains', istate(1:n)
        Write (nout,99996) 'and HESD contains', hesd(1:n)
      End Select

99999 Format (1X,A,4F12.4)
99998 Format (24X,1P,4E12.3)
99997 Format (1X,A,4I5)
99996 Format (1X,A,4E12.4)
    End Program e04kdfe