!   E04HDF Example Program Text
!   Mark 26.1 Release. NAG Copyright 2016.
    Module e04hdfe_mod

!     E04HDF 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, h
!     .. Parameters ..
      Integer, Parameter, Public       :: liw = 1, n = 4, nout = 6
      Integer, Parameter, Public       :: lh = n*(n-1)/2
      Integer, Parameter, Public       :: lw = 5*n
    Contains
      Subroutine funct(iflag,n,xc,fc,gc,iw,liw,w,lw)
!       Routine to evaluate objective function and its 1st derivatives.

!       .. 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 ..
        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
        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 h(iflag,n,xc,fhesl,lh,fhesd,iw,liw,w,lw)
!       Routine to evaluate 2nd derivatives

!       .. Scalar Arguments ..
        Integer, Intent (Inout)        :: iflag
        Integer, Intent (In)           :: lh, liw, lw, n
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: fhesd(n), w(lw)
        Real (Kind=nag_wp), Intent (Out) :: fhesl(lh)
        Real (Kind=nag_wp), Intent (In) :: xc(n)
        Integer, Intent (Inout)        :: iw(liw)
!       .. Executable Statements ..
        fhesd(1) = 2.0_nag_wp + 120.0_nag_wp*(xc(1)-xc(4))**2
        fhesd(2) = 200.0_nag_wp + 12.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3))**2
        fhesd(3) = 10.0_nag_wp + 48.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3))**2
        fhesd(4) = 10.0_nag_wp + 120.0_nag_wp*(xc(1)-xc(4))**2

        fhesl(1) = 20.0_nag_wp
        fhesl(2) = 0.0_nag_wp
        fhesl(3) = -24.0_nag_wp*(xc(2)-2.0_nag_wp*xc(3))**2
        fhesl(4) = -120.0_nag_wp*(xc(1)-xc(4))**2
        fhesl(5) = 0.0_nag_wp
        fhesl(6) = -10.0_nag_wp

        Return

      End Subroutine h
    End Module e04hdfe_mod
    Program e04hdfe

!     E04HDF Example Main Program

!     .. Use Statements ..
      Use e04hdfe_mod, Only: funct, h, lh, liw, lw, n, nout
      Use nag_library, Only: e04hcf, e04hdf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: f
      Integer                          :: i, ifail, k
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: g(n), hesd(n), hesl(lh), w(lw), x(n)
      Integer                          :: iw(liw)
!     .. Executable Statements ..
      Write (nout,*) 'E04HDF Example Program Results'

!     Set up an arbitrary point at which to check the derivatives

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

      Write (nout,*)
      Write (nout,*) 'The test point is'
      Write (nout,99999) x(1:n)

!     Check the 1st derivatives

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

!     Check the 2nd derivatives

      ifail = -1
      Call e04hdf(n,funct,h,x,g,hesl,lh,hesd,iw,liw,w,lw,ifail)

      If (ifail>=0) Then
        Write (nout,*)

        If (ifail==0) Then
          Write (nout,*) '2nd derivatives are consistent with 1st derivatives'
        Else If (ifail==2) Then
          Write (nout,*) 'Probable error in calculation of 2nd derivatives'
        End If

        Write (nout,*)
        Write (nout,99998) 'At the test point, FUNCT gives the function value' &
          , f
        Write (nout,*) 'and the 1st derivatives'
        Write (nout,99997) g(1:n)
        Write (nout,*)
        Write (nout,*) 'H gives the lower triangle of the Hessian matrix'
        Write (nout,99996) hesd(1)

        k = 1

        Do i = 2, n
          Write (nout,99996) hesl(k:(k+i-2)), hesd(i)
          k = k + i - 1
        End Do

      End If

99999 Format (1X,4F9.4)
99998 Format (1X,A,1P,E12.4)
99997 Format (1X,1P,4E12.3)
99996 Format (1X,1P,4E12.3)
    End Program e04hdfe