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

NAG FL Interface Introduction
Example description
!   E04JEF Example Program Text

    Program e04jefe

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nag_library, Only: e04jef, e04raf, e04rgf, e04rhf, e04rzf, e04zmf,   &
                             nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Real (Kind=nag_wp), Parameter    :: infbnd = 1.0E20_nag_wp
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Type (c_ptr)                     :: handle
      Integer                          :: i, ifail, irevcm, maxeval, neval,    &
                                          nvar
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: f(:), lx(:), ux(:), x(:,:)
      Real (Kind=nag_wp)               :: rinfo(100), stats(100)
      Integer, Allocatable             :: idxfd(:)
!     .. Executable Statements ..

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

      nvar = 4
      maxeval = 2

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

!     Define objective function as nonlinear
      Allocate (idxfd(nvar))
      idxfd(1:nvar) = (/(i,i=1,nvar)/)
      Call e04rgf(handle,nvar,idxfd,ifail)

!     Set options
!     relax the main convergence criteria a bit
      Call e04zmf(handle,'DFO Trust Region Tolerance = 5.0e-6',ifail)
!     Print the solution
      Call e04zmf(handle,'Print Solution = YES',ifail)
!     Set starting trust region (default was 0.1)
      Call e04zmf(handle,'DFO Starting trust Region = 0.2',ifail)

!     Define starting point
      Allocate (x(nvar,maxeval),f(maxeval))
      x(1:nvar,1) = (/3.0_nag_wp,-1.0_nag_wp,0.0_nag_wp,1.0_nag_wp/)

!     Define bounds for the variables
      Allocate (lx(nvar),ux(nvar))
      lx(1:nvar) = (/1.0_nag_wp,-2.0_nag_wp,-infbnd,1.0_nag_wp/)
      ux(1:nvar) = (/3.0_nag_wp,0.0_nag_wp,infbnd,3.0_nag_wp/)
      Call e04rhf(handle,nvar,lx,ux,ifail)

!     Call the solver in the reverse communication loop
      irevcm = 1
      Do While (irevcm/=0)
        ifail = -1
        Call e04jef(handle,irevcm,neval,maxeval,nvar,x,f,rinfo,stats,ifail)
        If (irevcm==1) Then
          Do i = 1, neval
!           Compute the rosenbrock objective function on the required points
            f(i) = (x(1,i)+10.0_nag_wp*x(2,i))**2 + 5.0_nag_wp*(x(3,i)-x(4,i)) &
              **2 + (x(2,i)-2.0_nag_wp*x(3,i))**4 + 10.0_nag_wp*(x(1,i)-x(4,i) &
              )**4
          End Do
        End If
      End Do

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

    End Program e04jefe