!   E04UHF Example Program Text
!   Mark 26.1 Release. NAG Copyright 2016.

    Module e04uhfe_mod

!     E04UHF 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                           :: objfun
!     .. Parameters ..
      Integer, Parameter, Public       :: iset = 1, nin = 5, ninopt = 7,       &
                                          nout = 6
    Contains
      Subroutine objfun(mode,nonln,x,objf,objgrd,nstate,iuser,ruser)
!       Computes the nonlinear part of the objective function and its
!       gradient

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: objf
        Integer, Intent (Inout)        :: mode
        Integer, Intent (In)           :: nonln, nstate
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: objgrd(nonln), ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(nonln)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Executable Statements ..
        If (mode==0 .Or. mode==2) Then
          objf = 2.0E+0_nag_wp - x(1)*x(2)*x(3)*x(4)*x(5)/120.0E+0_nag_wp
        End If

        If (mode==1 .Or. mode==2) Then
          objgrd(1) = -x(2)*x(3)*x(4)*x(5)/120.0E+0_nag_wp
          objgrd(2) = -x(1)*x(3)*x(4)*x(5)/120.0E+0_nag_wp
          objgrd(3) = -x(1)*x(2)*x(4)*x(5)/120.0E+0_nag_wp
          objgrd(4) = -x(1)*x(2)*x(3)*x(5)/120.0E+0_nag_wp
          objgrd(5) = -x(1)*x(2)*x(3)*x(4)/120.0E+0_nag_wp
        End If

        Return

      End Subroutine objfun
    End Module e04uhfe_mod
    Program e04uhfe

!     E04UHF Example Main Program

!     .. Use Statements ..
      Use e04uhfe_mod, Only: iset, nin, ninopt, nout, objfun
      Use nag_library, Only: e04ugf, e04ugm, e04uhf, e04ujf, nag_wp, x04abf,   &
                             x04acf, x04baf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Character (*), Parameter         :: fname = 'e04uhfe.opt'
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: obj, sinf
      Integer                          :: ifail, inform, iobj, leniz, lenz, m, &
                                          miniz, minz, mode, n, ncnln, ninf,   &
                                          njnln, nname, nnz, nonln, ns, outchn
      Character (80)                   :: rec
      Character (1)                    :: start
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: a(:), bl(:), bu(:), clamda(:),       &
                                          xs(:), z(:)
      Real (Kind=nag_wp)               :: user(1)
      Integer, Allocatable             :: ha(:), istate(:), iz(:), ka(:)
      Integer                          :: iuser(1)
      Character (8), Allocatable       :: names(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: max
!     .. Executable Statements ..
      Write (rec,99998) 'E04UHF Example Program Results'
      Call x04baf(nout,rec)

!     Skip heading in data file.
      Read (nin,*)
      Read (nin,*) n, m
      Read (nin,*) ncnln, nonln, njnln
      Read (nin,*) start, nname
      nnz = 1
      Allocate (ha(nnz),ka(n+1),istate(n+m),a(nnz),bl(n+m),bu(n+m),xs(n+m),    &
        clamda(n+m),names(nname))

      Read (nin,*) names(1:nname)

!     Define the matrix A to contain a dummy `free' row that consists
!     of a single (zero) element subject to `infinite' upper and
!     lower bounds. Set up KA.

      iobj = -1

      ka(1) = 1

      a(1) = 0.0E+0_nag_wp
      ha(1) = 1

!     Columns 2,3,...,N of A are empty. Set the corresponding element
!     of KA to 2.

      ka(2:n) = 2
      ka(n+1) = nnz + 1

      Read (nin,*) bl(1:(n+m))
      Read (nin,*) bu(1:(n+m))

      If (start=='C') Then
        Read (nin,*) istate(1:n)
      Else If (start=='W') Then
        Read (nin,*) istate(1:(n+m))
      End If

      Read (nin,*) xs(1:n)

!     Set the unit number for advisory messages to OUTCHN.

      outchn = nout
      Call x04abf(iset,outchn)

!     Set three options using E04UJF.

      Call e04ujf(' Verify Level = -1 ')

      Call e04ujf(' Major Iteration Limit = 25 ')

      Call e04ujf(' Infinite Bound Size = 1.0D+25 ')

!     Open the options file for reading

      mode = 0

      ifail = 0
      Call x04acf(ninopt,fname,mode,ifail)

!     Read the options file for the remaining options.

      Call e04uhf(ninopt,inform)

      If (inform/=0) Then
        Write (rec,99999) 'E04UJF terminated with INFORM = ', inform
        Call x04baf(nout,rec)
        Go To 100
      End If

!     Solve the problem.
!     First call is a workspace query

      leniz = max(500,n+m)
      lenz = 500
      Allocate (iz(leniz),z(lenz))

      ifail = 1
      Call e04ugf(e04ugm,objfun,n,m,ncnln,nonln,njnln,iobj,nnz,a,ha,ka,bl,bu,  &
        start,nname,names,ns,xs,istate,clamda,miniz,minz,ninf,sinf,obj,iz,     &
        leniz,z,lenz,iuser,user,ifail)

      If (ifail/=0 .And. ifail/=15 .And. ifail/=16) Then
        Write (nout,99999) 'Query call to E04UGF failed with IFAIL =', ifail
        Go To 100
      End If

      Deallocate (iz,z)

!     The length of the workspace required for the basis factors in this
!     problem is longer than the minimum returned by the query

      lenz = 2*minz
      leniz = 2*miniz
      Allocate (iz(leniz),z(lenz))

      ifail = 0
      Call e04ugf(e04ugm,objfun,n,m,ncnln,nonln,njnln,iobj,nnz,a,ha,ka,bl,bu,  &
        start,nname,names,ns,xs,istate,clamda,miniz,minz,ninf,sinf,obj,iz,     &
        leniz,z,lenz,iuser,user,ifail)
100   Continue

99999 Format (1X,A,I5)
99998 Format (1X,A)
    End Program e04uhfe