!   H02CEF Example Program Text
!   Mark 25 Release. NAG Copyright 2014.

    Module h02cefe_mod

!     H02CEF 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                               :: monit, qphx
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter        :: cutoff = -1847510.0_nag_wp
      Integer, Parameter, Public           :: lintvr = 10, mdepth = 2000,      &
                                              nin = 5, nout = 6
    Contains
      Subroutine qphx(nstate,ncolh,x,hx)

!       Routine to compute H*x. (In this version of QPHX, the Hessian
!       matrix H is not referenced explicitly.)

!       .. Scalar Arguments ..
        Integer, Intent (In)                 :: ncolh, nstate
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out)     :: hx(ncolh)
        Real (Kind=nag_wp), Intent (In)      :: x(ncolh)
!       .. Executable Statements ..
        If (nstate==1) Then
!         This is the first call.
!         Take any special action here if desired.
          Continue
        Else If (nstate>=2) Then
!         This is the last call.
          Continue
        End If
        hx(1:ncolh) = 2._nag_wp*x(1:ncolh)
        hx(3) = hx(3) + 2._nag_wp*x(4)
        hx(4) = hx(4) + 2._nag_wp*x(3)
        hx(6) = hx(6) + 2._nag_wp*x(7)
        hx(7) = hx(7) + 2._nag_wp*x(6)
        Return
      End Subroutine qphx
      Subroutine monit(intfnd,nodes,depth,obj,x,bstval,bstsol,bl,bu,n,halt, &
        count)

!       .. Scalar Arguments ..
        Real (Kind=nag_wp), Intent (Inout)   :: bstval
        Real (Kind=nag_wp), Intent (In)      :: obj
        Integer, Intent (Inout)              :: count
        Integer, Intent (In)                 :: depth, intfnd, n, nodes
        Logical, Intent (Inout)              :: halt
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (In)      :: bl(n), bstsol(n), bu(n), x(n)
!       .. Executable Statements ..
        If (intfnd==0) Then
          bstval = cutoff
        Else If (intfnd>count) Then
          Write (nout,*) 'New integer solution found'
          Write (nout,99999) '  Nodes solved so far: ', nodes
          Write (nout,99999) '  Reached depth: ', depth
          Write (nout,99998) '  Solution value at current node: ', obj
          Write (nout,*) '  Solution vector at current node:'
          Write (nout,99997) x(1:n)
          Write (nout,99998) '  Current best function value: ', bstval
          Write (nout,*) '  Current best solution:'
          Write (nout,99997) bstsol(1:n)
          Write (nout,*) '  Current lower bounds:'
          Write (nout,99997) bl(1:n)
          Write (nout,*) '  Current upper bounds:'
          Write (nout,99997) bu(1:n)
        End If
        count = intfnd
!       Set halt .True. to terminate execution for any reason.
        halt = .False.
        Return
99999   Format (1X,A,I20)
99998   Format (1X,A,E13.5)
99997   Format (1X,2X,E13.5)
      End Subroutine monit
    End Module h02cefe_mod
    Program h02cefe

!     H02CEF Example Main Program

!     .. Use Statements ..
      Use nag_library, Only: h02cef, h02cgf, nag_wp
      Use h02cefe_mod, Only: lintvr, mdepth, monit, nin, nout, qphx
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)                   :: obj
      Integer                              :: i, icol, ifail, iobj, jcol,      &
                                              leniz, lenz, m, miniz, minz, n,  &
                                              ncolh, nname, nnz, ns, strtgy
      Character (1)                        :: start
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable      :: a(:), bl(:), bu(:), clamda(:),   &
                                              xs(:), z(:)
      Integer, Allocatable                 :: ha(:), intvar(:), istate(:),     &
                                              iz(:), ka(:)
      Character (8), Allocatable           :: crname(:)
      Character (8)                        :: names(5)
!     .. Executable Statements ..
      Write (nout,*) 'H02CEF Example Program Results'

!     Skip heading in data file.
      Read (nin,*)

      Read (nin,*) n, m
      Read (nin,*) nnz, iobj, ncolh, start, nname
      Allocate (a(nnz),bl(n+m),bu(n+m),clamda(n+m),xs(n+m),ha(nnz), &
        intvar(lintvr),istate(n+m),ka(n+1),crname(nname))

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

!     Read the matrix A from data file. Set up KA.

      jcol = 1
      ka(jcol) = 1

      Do i = 1, nnz

!       Element ( HA( I ), ICOL ) is stored in A( I ).

        Read (nin,*) a(i), ha(i), icol

        If (icol==jcol+1) Then

!         Index in A of the start of the ICOL-th column equals I.

          ka(icol) = i
          jcol = icol
        Else If (icol>jcol+1) Then

!         Index in A of the start of the ICOL-th column equals I,
!         but columns JCOL+1,JCOL+2,...,ICOL-1 are empty. Set the
!         corresponding elements of KA to I.

          ka((jcol+1):(icol-1)) = i
          ka(icol) = i
          jcol = icol
        End If

      End Do

      ka(n+1) = nnz + 1

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

      strtgy = 3
      intvar(1:7) = (/2,3,4,5,6,7,-1/)

      Call h02cgf('NoList')

      Call h02cgf('Print Level = 0')

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

      leniz = 1
      lenz = 1
      Allocate (iz(leniz),z(lenz))

      ifail = 1
      Call h02cef(n,m,nnz,iobj,ncolh,qphx,a,ha,ka,bl,bu,start,names,nname, &
        crname,ns,xs,intvar,lintvr,mdepth,istate,miniz,minz,obj,clamda,strtgy, &
        iz,leniz,z,lenz,monit,ifail)

      If (ifail/=14) Then
        Write (nout,99998) ifail
      Else
        Deallocate (iz,z)

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

        ifail = 0
        Call h02cef(n,m,nnz,iobj,ncolh,qphx,a,ha,ka,bl,bu,start,names,nname, &
          crname,ns,xs,intvar,lintvr,mdepth,istate,miniz,minz,obj,clamda, &
          strtgy,iz,leniz,z,lenz,monit,ifail)

!       Print out the best integer solution found

        Write (nout,99999) obj, (i,xs(i),i=1,n)
      End If

99999 Format (' Optimal Integer Value is = ',E20.8/' Components are '/(' X(', &
        I3,') = ',F10.2))
99998 Format (1X,'** Workspace query in H02CEF exited with IFAIL = ',I0)
    End Program h02cefe