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

NAG FL Interface Introduction
Example description
!   E04JDF Example Program Text

    Module e04jdfe_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,fx,inform,iuser,ruser,cpuser)

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

        fx = (x(1)+10.0_nag_wp*x(2))**2 + 5.0_nag_wp*(x(3)-x(4))**2 +          &
          (x(2)-2.0_nag_wp*x(3))**4 + 10.0_nag_wp*(x(1)-x(4))**4
      End Subroutine objfun

    End Module e04jdfe_mod


    Program e04jdfe

!     Mark 28.5 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use e04jdfe_mod, Only: objfun
      Use iso_c_binding, Only: c_null_ptr, c_ptr
      Use nag_library, Only: e04jdf, e04jdu, 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)                     :: cpuser, handle
      Integer                          :: i, ifail, nvar
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: lx(:), ux(:), x(:)
      Real (Kind=nag_wp)               :: rinfo(100), ruser(1), stats(100)
      Integer, Allocatable             :: idxfd(:)
      Integer                          :: iuser(1)
!     .. Executable Statements ..

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

      nvar = 4
      cpuser = c_null_ptr

!     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))
      x(1:nvar) = (/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
      Call e04jdf(handle,objfun,e04jdu,nvar,x,rinfo,stats,iuser,ruser,cpuser,  &
        ifail)

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

    End Program e04jdfe