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

NAG FL Interface Introduction
Example description
!   E04RMF Example Program Text

!   Mark 28.4 Release. NAG Copyright 2022.

    Module e04rmfe_mod

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: objfun

    Contains

      Subroutine objfun(nvar,x,nres,rx,inform,iuser,ruser,cpuser)

!       .. Scalar Arguments ..
        Type (c_ptr), Intent (In)      :: cpuser
        Integer, Intent (Inout)        :: inform
        Integer, Intent (In)           :: nres, nvar
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Real (Kind=nag_wp), Intent (Out) :: rx(nres)
        Real (Kind=nag_wp), Intent (In) :: x(nvar)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Executable Statements ..

!       Interrupt solver if the dimensions are incorrect
        If (nres/=3 .Or. nvar/=2) Then
          inform = -1
          Go To 100
        End If

        rx(1) = x(1) + x(2) - 1.1_nag_wp
        rx(2) = 2.0_nag_wp*x(1) + x(2) - 1.9_nag_wp
        rx(3) = 3.0_nag_wp*x(1) + x(2) - 3.0_nag_wp

100     Continue
        Return

      End Subroutine objfun

    End Module e04rmfe_mod


    Program e04rmfe

!     .. Use Statements ..
      Use e04rmfe_mod, Only: objfun
      Use iso_c_binding, Only: c_null_ptr, c_ptr
      Use nag_library, Only: e04fff, e04ffu, e04raf, e04rmf, e04rzf, e04zmf,   &
                             nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Type (c_ptr)                     :: cpuser, handle
      Integer                          :: ifail, isparse, nnzrd, nres, nvar
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: rinfo(100), ruser(1), stats(100)
      Real (Kind=nag_wp), Allocatable  :: rx(:), x(:)
      Integer                          :: icolrd(6), irowrd(6), iuser(1)
!     .. Executable Statements ..

      Write (nout,*) 'E04RMF Example Program Results'
      Write (nout,*)
      Flush (nout)

      nvar = 2
      nres = 3
      handle = c_null_ptr

!     Initialize handle
      ifail = 0
      Call e04raf(handle,nvar,ifail)

!     Define residuals structure with e04rmf
      isparse = 1
      nnzrd = 6
      icolrd(1:6) = (/1,1,2,2,3,3/)
      irowrd(1:6) = (/1,2,1,2,1,2/)
      Call e04rmf(handle,nres,isparse,nnzrd,irowrd,icolrd,ifail)

!     Set options for the e04fff solver
!     relax the main convergence criteria a bit
      Call e04zmf(handle,'DFLS Trust Region Tolerance = 1.0e-03',ifail)
!     Deactivate the slow iterations detection
      Call e04zmf(handle,'DFLS Maximum Slow Steps = 0',ifail)
!     Turn off option printing
      Call e04zmf(handle,'Print Options = NO',ifail)
!     Print the solution
      Call e04zmf(handle,'Print Solution = YES',ifail)
!     Deactivate iteration log
      Call e04zmf(handle,'Print Level = 1',ifail)

!     Define starting point
      Allocate (x(nvar),rx(nres))
      x(1:2) = (/2.0_nag_wp,2.0_nag_wp/)

!     Call the solver
      ifail = -1
      cpuser = c_null_ptr
      Call e04fff(handle,objfun,e04ffu,nvar,x,nres,rx,rinfo,stats,iuser,ruser, &
        cpuser,ifail)

!     Free the handle memory
      ifail = 0
      Call e04rzf(handle,ifail)

    End Program e04rmfe