! D02PE_A1T1W_F Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
Module d02pe_a1t1w_fe_mod
! D02PE_A1T1W_F Example Program Module:
! Parameters and User-defined Routines
! .. Use Statements ..
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: nagad_a1t1w_w_rtype, Assignment (=), &
Operator (-)
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: f
! .. Parameters ..
Integer, Parameter, Public :: liwsav = 130, n = 2, nin = 5, &
nout = 6, npts = 8
Integer, Parameter, Public :: lrwsav = 350 + 32*n
Contains
Subroutine f(ad_handle,t,n,y,yp,iuser,ruser)
! .. Implicit None Statement ..
Implicit None
! .. Scalar Arguments ..
Type (c_ptr), Intent (Inout) :: ad_handle
Type (nagad_a1t1w_w_rtype), Intent (In) :: t
Integer, Intent (In) :: n
! .. Array Arguments ..
Type (nagad_a1t1w_w_rtype), Intent (Inout) :: ruser(*)
Type (nagad_a1t1w_w_rtype), Intent (In) :: y(n)
Type (nagad_a1t1w_w_rtype), Intent (Out) :: yp(n)
Integer, Intent (Inout) :: iuser(*)
! .. Executable Statements ..
yp(1) = y(2)
yp(2) = -y(1)
Return
End Subroutine f
End Module d02pe_a1t1w_fe_mod
Program d02pe_a1t1w_fe
! D02PE_A1T1W_F Example Main Program
! .. Use Statements ..
Use d02pe_a1t1w_fe_mod, Only: f, liwsav, lrwsav, n, nin, nout, npts
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: d02pe_a1t1w_f, d02pq_a1t1w_f, d02pt_a1t1w_f, &
nagad_a1t1w_get_derivative, &
nagad_a1t1w_inc_derivative, &
nagad_a1t1w_ir_interpret_adjoint, &
nagad_a1t1w_ir_register_variable, &
nagad_a1t1w_ir_remove, nagad_a1t1w_w_rtype, &
nagad_t1w_w_rtype, x10aa_a1t1w_f, &
x10ab_a1t1w_f, x10za_a1t1w_f, Operator (+), &
Assignment (=)
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Type (c_ptr) :: ad_handle
Type (nagad_a1t1w_w_rtype) :: hnext, hs, te, tgot, tinc, tol, ts, &
twant, waste
Type (nagad_t1w_w_rtype) :: t_t
Real (Kind=nag_wp) :: dr, hstart, t, tend, tolr, tstart
Integer :: fevals, ifail, j, method, stepcost, &
stepsok
! .. Local Arrays ..
Type (nagad_a1t1w_w_rtype) :: ruser(1), th(n), y(n), ygot(n), &
yin(n), ymax(n), ypgot(n)
Type (nagad_a1t1w_w_rtype), Allocatable :: rwsav(:)
Real (Kind=nag_wp) :: thresh(n), yinit(n), yr(n)
Integer :: iuser(1)
Integer, Allocatable :: iwsav(:)
! .. Intrinsic Procedures ..
Intrinsic :: real
! .. Executable Statements ..
Write (nout,*) 'D02PE_A1T1W_F Example Program Results'
Allocate (iwsav(liwsav),rwsav(lrwsav))
! Set initial conditions and input
! Skip heading in data file
Read (nin,*)
Read (nin,*) method
Read (nin,*) tstart, tend
Read (nin,*) yinit(1:n)
Read (nin,*) hstart
Read (nin,*) thresh(1:n)
! Set control for output
tinc = (tend-tstart)/real(npts,kind=nag_wp)
tolr = 1.0E-4_nag_wp
ts = tstart
te = tend
yin(1:n) = yinit(1:n)
tol = tolr
th(1:n) = thresh(1:n)
hs = hstart
! Create AD tape
Call x10za_a1t1w_f
! Create AD configuration data object
ifail = 0
Call x10aa_a1t1w_f(ad_handle,ifail)
! Register variables to differentiate w.r.t.
yin(1:n)%value%tangent = 1.0_nag_wp
Call nagad_a1t1w_ir_register_variable(yin)
y(1:n) = yin(1:n)
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call d02pq_a1t1w_f(ad_handle,n,ts,te,y,tol,th,method,hs,iwsav,rwsav, &
ifail)
Write (nout,99999) tolr
Write (nout,99998)
Write (nout,99997) tstart, yinit(1:n)
twant = tstart
Do j = 1, npts
twant = twant + tinc
ifail = 0
Call d02pe_a1t1w_f(ad_handle,f,n,twant,tgot,ygot,ypgot,ymax,iuser, &
ruser,iwsav,rwsav,ifail)
t = tgot%value
yr(1:n) = ygot(1:n)%value
Write (nout,99997) t, yr(1:n)
End Do
ifail = 0
Call d02pt_a1t1w_f(ad_handle,fevals,stepcost,waste,stepsok,hnext,iwsav, &
rwsav,ifail)
Write (nout,99996) fevals
99999 Format (/,' Calculation with TOL = ',1P,E8.1)
99998 Format (/,' t y1 y2',/)
99997 Format (1X,F6.3,2(3X,F7.3))
99996 Format (/,' Cost of the integration in evaluations of F is',I6)
t_t%value = 1.0_nag_wp
t_t%tangent = 0.0_nag_wp
Do j = 1, n
Call nagad_a1t1w_inc_derivative(ygot(j),t_t)
End Do
Call nagad_a1t1w_ir_interpret_adjoint(ifail)
Write (nout,*)
Write (nout,*) &
' Derivatives calculated: Second order, adjoints of tangents'
Write (nout,*) ' Computational mode : algorithmic'
! Get derivatives
dr = 0.0_nag_wp
Do j = 1, n
t_t = nagad_a1t1w_get_derivative(yin(j))
dr = dr + t_t%tangent
End Do
Write (nout,*) ' Sum of Hessian terms for y w.r.t. its initial values:'
Write (nout,99995) ' Sum_{i,j,k} d^2y_k/d(y0_i)d(y0_j) =', dr
99995 Format (1X,A,1X,E12.5)
! Remove computational data object and tape
ifail = 0
Call x10ab_a1t1w_f(ad_handle,ifail)
Call nagad_a1t1w_ir_remove
End Program d02pe_a1t1w_fe