!   C05RBF Example Program Text
!   Mark 26.1 Release. NAG Copyright 2017.

    Module c05rbfe_mod

!     C05RBF 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 ..
      Integer, Parameter, Public       :: n = 9, nout = 6
    Contains
      Subroutine fcn(n,x,fvec,fjac,iuser,ruser,iflag)

!       .. Parameters ..
        Real (Kind=nag_wp), Parameter  :: coeff(5) = (/-1.0_nag_wp,3.0_nag_wp, &
                                          -2.0_nag_wp,-2.0_nag_wp,             &
                                          -1.0_nag_wp/)
!       .. Scalar Arguments ..
        Integer, Intent (Inout)        :: iflag
        Integer, Intent (In)           :: n
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: fjac(n,n), fvec(n), ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(n)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Integer                        :: k
!       .. Executable Statements ..
        If (iflag/=2) Then
          fvec(1:n) = (coeff(2)+coeff(3)*x(1:n))*x(1:n) - coeff(5)
          fvec(2:n) = fvec(2:n) + coeff(1)*x(1:(n-1))
          fvec(1:(n-1)) = fvec(1:(n-1)) + coeff(4)*x(2:n)
        Else
          fjac(1:n,1:n) = 0.0_nag_wp
          fjac(1,1) = coeff(2) + 2.0_nag_wp*coeff(3)*x(1)
          fjac(1,2) = coeff(4)
          Do k = 2, n - 1
            fjac(k,k-1) = coeff(1)
            fjac(k,k) = coeff(2) + 2.0_nag_wp*coeff(3)*x(k)
            fjac(k,k+1) = coeff(4)
          End Do
          fjac(n,n-1) = coeff(1)
          fjac(n,n) = coeff(2) + 2.0_nag_wp*coeff(3)*x(n)
        End If
!       Set iflag negative to terminate execution for any reason.
        iflag = 0
        Return
      End Subroutine fcn
    End Module c05rbfe_mod
    Program c05rbfe

!     C05RBF Example Main Program

!     .. Use Statements ..
      Use c05rbfe_mod, Only: fcn, n, nout
      Use nag_library, Only: c05rbf, dnrm2, nag_wp, x02ajf
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: fnorm, xtol
      Integer                          :: i, ifail
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: fjac(:,:), fvec(:), x(:)
      Real (Kind=nag_wp)               :: ruser(1)
      Integer                          :: iuser(1)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: sqrt
!     .. Executable Statements ..
      Write (nout,*) 'C05RBF Example Program Results'

      Allocate (fjac(n,n),fvec(n),x(n))

!     The following starting values provide a rough solution.

      x(1:n) = -1.0E0_nag_wp

      xtol = sqrt(x02ajf())

      ifail = -1
      Call c05rbf(fcn,n,x,fvec,fjac,xtol,iuser,ruser,ifail)

      If (ifail==0 .Or. ifail==2 .Or. ifail==3 .Or. ifail==4) 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,*) 'Final approximate solution'
        Else
          Write (nout,*)
          Write (nout,*) 'Approximate solution'
        End If
        Write (nout,*)
        Write (nout,99998)(x(i),i=1,n)
      End If

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