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

NAG FL Interface Introduction
Example description
!   E04NKF Example Program Text
!   Mark 28.5 Release. NAG Copyright 2022.

    Module e04nkfe_mod

!     E04NKF 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                           :: qphx
!     .. Parameters ..
      Integer, Parameter, Public       :: 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 ..
        hx(1) = 2.0E0_nag_wp*x(1)
        hx(2) = 2.0E0_nag_wp*x(2)
        hx(3) = 2.0E0_nag_wp*(x(3)+x(4))
        hx(4) = hx(3)
        hx(5) = 2.0E0_nag_wp*x(5)
        hx(6) = 2.0E0_nag_wp*(x(6)+x(7))
        hx(7) = hx(6)

        Return

      End Subroutine qphx
    End Module e04nkfe_mod
    Program e04nkfe

!     E04NKF Example Main Program

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

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

      Read (nin,*) n, m
      Read (nin,*) nnz, iobj, ncolh, start, nname
      Allocate (ha(nnz),ka(n+1),istate(n+m),a(nnz),bl(n+m),bu(n+m),xs(n+m),    &
        clamda(n+m),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) Then

!         Elements not ordered by increasing column index.

          Write (nout,99999) 'Element in column', icol,                        &
            ' found after element in column', jcol, '. Problem', ' abandoned.'
          Go To 100
        Else 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) = i
          jcol = icol
        End If

      End Do

      ka(n+1) = nnz + 1

!     Columns N,N-1,...,ICOL+1 are empty. Set the corresponding
!     elements of KA accordingly.

      Do i = n, icol + 1, -1
        ka(i) = ka(i+1)
      End Do

      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)

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

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

      ifail = 1
      Call e04nkf(n,m,nnz,iobj,ncolh,qphx,a,ha,ka,bl,bu,start,names,nname,     &
        crname,ns,xs,istate,miniz,minz,ninf,sinf,obj,clamda,iz,leniz,z,lenz,   &
        ifail)

      If (ifail/=0 .And. ifail/=12 .And. ifail/=13) Then
        Write (nout,99998) 'Query call to E04NKF failed with IFAIL =', ifail
        Go To 100
      End If

      Deallocate (iz,z)

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

      ifail = 0
      Call e04nkf(n,m,nnz,iobj,ncolh,qphx,a,ha,ka,bl,bu,start,names,nname,     &
        crname,ns,xs,istate,miniz,minz,ninf,sinf,obj,clamda,iz,leniz,z,lenz,   &
        ifail)

100   Continue

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