Example description
!   C05MBF Example Program Text
!   Mark 27.1 Release. NAG Copyright 2020.

    Module c05mbfe_mod

!     C05MBF Example Program Module:

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: fcn
!     .. Parameters ..
      Integer, Parameter, Public       :: n = 4, nout = 6
    Contains
      Subroutine fcn(n,x,fvec,iuser,ruser,cpuser,iflag)

!       .. Scalar Arguments ..
        Type (c_ptr), Intent (In)      :: cpuser
        Integer, Intent (Inout)        :: iflag
        Integer, Intent (In)           :: n
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: fvec(n)
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(n)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Intrinsic Procedures ..
        Intrinsic                      :: cos, sin, sqrt
!       .. Executable Statements ..
        fvec(1) = cos(x(3)) - x(1)
        fvec(2) = sqrt(1.0_nag_wp-x(4)**2) - x(2)
        fvec(3) = sin(x(1)) - x(3)
        fvec(4) = x(2)**2 - x(4)
!       Set iflag negative to terminate execution for any reason.
        iflag = 0
        Return
      End Subroutine fcn
    End Module c05mbfe_mod
    Program c05mbfe

!     C05MBF Example Main Program

!     .. Use Statements ..
      Use c05mbfe_mod, Only: fcn, n, nout
      Use iso_c_binding, Only: c_null_ptr, c_ptr
      Use nag_library, Only: c05mbf, dnrm2, nag_wp, x02ajf
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Type (c_ptr)                     :: cpuser
      Real (Kind=nag_wp)               :: atol, cndtol, fnorm, rtol
      Integer                          :: astart, i, ifail, m
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: fvec(:), x(:)
      Real (Kind=nag_wp)               :: ruser(1)
      Integer                          :: iuser(1)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: sqrt
!     .. Executable Statements ..
      Write (nout,*) 'C05MBF Example Program Results'

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

!     The following starting values provide a rough solution.

      x(1) = 2.0E0_nag_wp
      x(2) = 0.5E0_nag_wp
      x(3) = 2.0E0_nag_wp
      x(4) = 0.5E0_nag_wp

      m = 2
      atol = sqrt(x02ajf())
      rtol = sqrt(x02ajf())
      cndtol = 0.0_nag_wp
      astart = 0
      cpuser = c_null_ptr

      ifail = -1
      Call c05mbf(fcn,n,x,fvec,atol,rtol,m,cndtol,astart,iuser,ruser,cpuser,   &
        ifail)

      If (ifail==0 .Or. ifail==8 .Or. ifail==9) 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,4F12.4)
    End Program c05mbfe