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

NAG FL Interface Introduction
Example description
    Program c05qdfe

!     C05QDF Example Program Text

!     Mark 27.2 Release. NAG Copyright 2021.

!     .. Use Statements ..
      Use nag_library, Only: c05qdf, dnrm2, nag_wp, x02ajf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: n = 9, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: epsfcn, factor, fnorm, xtol
      Integer                          :: i, icount, ifail, irevcm, ml, mode,  &
                                          mu
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: diag(:), fjac(:,:), fvec(:), qtf(:), &
                                          r(:), rwsav(:), x(:)
      Integer, Allocatable             :: iwsav(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: sqrt
!     .. Executable Statements ..
      Write (nout,*) 'C05QDF Example Program Results'

      Allocate (diag(n),fjac(n,n),fvec(n),qtf(n),r(n*(n+                       &
        1)/2),rwsav(4*n+10),iwsav(17),x(n))

!     The following starting values provide a rough solution.

      x(1:n) = -1.0E0_nag_wp
      xtol = sqrt(x02ajf())
      diag(1:n) = 1.0E0_nag_wp
      ml = 1
      mu = 1
      epsfcn = 0.0E0_nag_wp
      mode = 2
      factor = 100.0E0_nag_wp
      icount = 0
      irevcm = 0
      ifail = -1

revcomm: Do

        Call c05qdf(irevcm,n,x,fvec,xtol,ml,mu,epsfcn,mode,diag,factor,fjac,r, &
          qtf,iwsav,rwsav,ifail)

        Select Case (irevcm)
        Case (1)
          icount = icount + 1

!         Insert print statements here to monitor progress if desired.

          Cycle revcomm
        Case (2)

!         Evaluate functions at given point

          fvec(1:n) = (3.0E0_nag_wp-2.0E0_nag_wp*x(1:n))*x(1:n) + 1.0E0_nag_wp
          fvec(2:n) = fvec(2:n) - x(1:(n-1))
          fvec(1:(n-1)) = fvec(1:(n-1)) - 2.0E0_nag_wp*x(2:n)
          Cycle revcomm
        Case Default
          Exit revcomm
        End Select

      End Do revcomm

      If (ifail==0 .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 after', icount,    &
            ' iterations is ', 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,I4,A,E12.4)
99998 Format (5X,3F12.4)
    End Program c05qdfe