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

    Module c05qcfe_mod

!     C05QCF 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                               :: fcn
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter, Public :: epsfcn = 0.0_nag_wp
      Real (Kind=nag_wp), Parameter, Public :: factor = 100.0_nag_wp
      Integer, Parameter, Public           :: maxfev = 2000, ml = 1, mode = 2, &
                                              mu = 1, n = 9, nout = 6,         &
                                              nprint = 0
    Contains
      Subroutine fcn(n,x,fvec,iuser,ruser,iflag)

!       .. Scalar Arguments ..
        Integer, Intent (Inout)              :: iflag
        Integer, Intent (In)                 :: n
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout)   :: fvec(n), ruser(*)
        Real (Kind=nag_wp), Intent (In)      :: x(n)
        Integer, Intent (Inout)              :: iuser(*)
!       .. Executable Statements ..
        If (iflag==0) Then
          If (nprint>0) Then
!           Insert print statements here if desired.
            Continue
          End If
        Else
          fvec(1:n) = (3.0_nag_wp-2.0_nag_wp*x(1:n))*x(1:n) + 1.0_nag_wp
          fvec(2:n) = fvec(2:n) - x(1:(n-1))
          fvec(1:(n-1)) = fvec(1:(n-1)) - 2.0_nag_wp*x(2:n)
        End If
!       Set iflag negative to terminate execution for any reason.
        iflag = 0
        Return
      End Subroutine fcn
    End Module c05qcfe_mod
    Program c05qcfe

!     C05QCF Example Main Program

!     .. Use Statements ..
      Use nag_library, Only: c05qcf, dnrm2, nag_wp, x02ajf
      Use c05qcfe_mod, Only: epsfcn, factor, fcn, maxfev, ml, mode, mu, n,     &
                             nout, nprint
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)                   :: fnorm, xtol
      Integer                              :: i, ifail, nfev
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable      :: diag(:), fjac(:,:), fvec(:),     &
                                              qtf(:), r(:), x(:)
      Real (Kind=nag_wp)                   :: ruser(1)
      Integer                              :: iuser(1)
!     .. Intrinsic Procedures ..
      Intrinsic                            :: sqrt
!     .. Executable Statements ..
      Write (nout,*) 'C05QCF Example Program Results'

      Allocate (diag(n),fjac(n,n),fvec(n),qtf(n),r(n*(n+1)/2),x(n))

!     The following starting values provide a rough solution.

      x(1:n) = -1.0_nag_wp
      xtol = sqrt(x02ajf())
      diag(1:n) = 1.0_nag_wp

      ifail = -1
      Call c05qcf(fcn,n,x,fvec,xtol,maxfev,ml,mu,epsfcn,mode,diag,factor, &
        nprint,nfev,fjac,r,qtf,iuser,ruser,ifail)

      If (ifail==0 .Or. ifail==2 .Or. ifail==3 .Or. ifail==4 .Or. ifail==5) &
        Then
        If (ifail==0) Then
!         The NAG name equivalent of dnrm2 is f06ejf
          fnorm = dnrm2(n,fvec,1)
          Write (nout,*)
          Write (nout,99999) 'Final 2-norm of the residuals =', fnorm
          Write (nout,*)
          Write (nout,99998) 'Number of function evaluations =', nfev
          Write (nout,*)
          Write (nout,*) 'Final approximate solution'
        Else
          Write (nout,*)
          Write (nout,*) 'Approximate solution'
        End If
        Write (nout,*)
        Write (nout,99997)(x(i),i=1,n)
      End If

99999 Format (1X,A,E12.4)
99998 Format (1X,A,I10)
99997 Format (1X,3F12.4)
    End Program c05qcfe