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

NAG AD Library Introduction
Example description
!   E04DG_P0W_F Example Program Text
!   Mark 29.3 Release. NAG Copyright 2023.

    Module e04dg_p0w_fe_mod

!     E04DG_P0W_F Example Program Module:
!            Parameters and User-defined Routines

!     .. 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
!     .. Parameters ..
      Integer, Parameter, Public       :: nin = 5, nout = 6
    Contains
      Subroutine objfun(ad_handle,mode,n,x,objf,objgrd,nstate,iuser,ruser)

!       .. Scalar Arguments ..
        Type (c_ptr), Intent (Inout)   :: ad_handle
        Real (Kind=nag_wp), Intent (Out) :: objf
        Integer, Intent (Inout)        :: mode
        Integer, Intent (In)           :: n, nstate
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: objgrd(n)
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(n)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Local Scalars ..
        Real (Kind=nag_wp)             :: expx1, x1, x2, y1, y2
!       .. Intrinsic Procedures ..
        Intrinsic                      :: exp
!       .. Executable Statements ..
        x1 = x(1)
        x2 = x(2)
        expx1 = exp(x1)
        y1 = 2.0_nag_wp*x1 + x2
        y2 = x2 + 1.0_nag_wp
        objf = expx1*(y1*y1+y2*y2)

        If (mode==2) Then
          objgrd(1) = expx1*(4.0_nag_wp*y1) + objf
          objgrd(2) = expx1*(2.0_nag_wp*(y1+y2))
        End If

        Return

      End Subroutine objfun
    End Module e04dg_p0w_fe_mod
    Program e04dg_p0w_fe

!     E04DG_P0W_F Example Main Program

!     .. Use Statements ..
      Use e04dg_p0w_fe_mod, Only: nin, nout, objfun
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: e04dg_p0w_f
      Use nag_library, Only: e04wbf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Real (Kind=nag_wp)               :: objf
      Integer                          :: ifail, iter, n
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: objgrd(:), work(:), x(:)
      Real (Kind=nag_wp)               :: ruser(1), rwsav(475)
      Integer                          :: iuser(1), iwsav(610)
      Integer, Allocatable             :: iwork(:)
      Logical                          :: lwsav(120)
      Character (80)                   :: cwsav(1)
!     .. Executable Statements ..
      Write (nout,*) 'E04DG_P0W_F Example Program Results'
      Flush (nout)

!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n

      Allocate (iwork(n+1),objgrd(n),x(n),work(13*n))

      Read (nin,*) x(1:n)

!     Initialize sav arrays
      ifail = 0
      Call e04wbf('E04DGA',cwsav,1,lwsav,120,iwsav,610,rwsav,475,ifail)

!     Solve the problem
      ifail = 0
      Call e04dg_p0w_f(ad_handle,n,objfun,iter,objf,objgrd,x,iwork,work,iuser, &
        ruser,lwsav,iwsav,rwsav,ifail)

    End Program e04dg_p0w_fe