Example description
!   H02CFF Example Program Text
!   Mark 27.0 Release. NAG Copyright 2019.

    Module h02cffe_mod

!     H02CFF 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 = -1840000.0_nag_wp
      Integer, Parameter, Public       :: iset = 1, lintvr = 10,               &
                                          mdepth = 2000, nin = 5, ninopt = 7,  &
                                          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 ..
        hx(1) = 2.0_nag_wp*x(1)
        hx(2) = 2.0_nag_wp*x(2)
        hx(3) = 2.0_nag_wp*(x(3)+x(4))
        hx(4) = hx(3)
        hx(5) = 2.0_nag_wp*x(5)
        hx(6) = 2.0_nag_wp*(x(6)+x(7))
        hx(7) = hx(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
        End If

        Return

      End Subroutine monit
    End Module h02cffe_mod
    Program h02cffe

!     H02CFF Example Main Program

!     .. Use Statements ..
      Use h02cffe_mod, Only: iset, lintvr, mdepth, monit, nin, ninopt, nout,   &
                             qphx
      Use nag_library, Only: h02cef, h02cff, h02cgf, nag_wp, x04abf, x04acf,   &
                             x04baf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Character (*), Parameter         :: fname = 'h02cffe.opt'
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: obj
      Integer                          :: i, icol, ifail, inform, iobj, jcol,  &
                                          leniz, lenz, m, miniz, minz, mode,   &
                                          n, ncolh, nname, nnz, ns, outchn,    &
                                          strtgy
      Character (200)                  :: rec
      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 (rec,99996) 'H02CFF Example Program Results'
      Call x04baf(nout,rec)

!     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)

!     Set three options using H02CGF.

      Call h02cgf(' Check Frequency = 10 ')

      Call h02cgf(' Feasibility Tolerance = 0.00001 ')

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

!     Set the unit number for advisory messages to OUTCHN.

      outchn = nout

      Call x04abf(iset,outchn)

!     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 h02cff(ninopt,inform)

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

      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 (rec,99995) ifail
        Call x04baf(nout,rec)
      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 (rec,99999) obj
        Call x04baf(nout,rec)
        Call x04baf(nout,' Components are')

        Do i = 1, n
          Write (rec,99998) i, xs(i)
          Call x04baf(nout,rec)
        End Do

      End If

100   Continue

99999 Format (1X,'Optimal Integer Value is = ',E20.8)
99998 Format (1X,'X(',I3,') = ',F10.2)
99997 Format (A,I5)
99996 Format (1X,A)
99995 Format (1X,'** Workspace query in H02CEF exited with IFAIL = ',I0)
    End Program h02cffe