! D02PU_T2W_F Example Program Text
! Mark 30.1 Release. NAG Copyright 2024.
Module d02pu_t2w_fe_mod
! D02PU_T2W_F Example Program Module:
! Parameters and User-defined Routines
! .. Use Statements ..
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: nagad_t2w_w_rtype, sqrt, Operator (/), &
Operator (+), Operator (*), Operator (**), &
Operator (-)
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: f
! .. Parameters ..
Integer, Parameter, Public :: liwsav = 130, n = 4, nin = 5, &
nout = 6
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_t2w_w_rtype), Intent (In) :: t
Integer, Intent (In) :: n
! .. Array Arguments ..
Type (nagad_t2w_w_rtype), Intent (Inout) :: ruser(*)
Type (nagad_t2w_w_rtype), Intent (In) :: y(n)
Type (nagad_t2w_w_rtype), Intent (Out) :: yp(n)
Integer, Intent (Inout) :: iuser(*)
! .. Local Scalars ..
Type (nagad_t2w_w_rtype) :: r
! .. Executable Statements ..
r = 1.0_nag_wp/sqrt(y(1)*y(1)+y(2)*y(2))
r = r**3
yp(1) = y(3)
yp(2) = y(4)
yp(3) = -y(1)*r
yp(4) = -y(2)*r
Return
End Subroutine f
End Module d02pu_t2w_fe_mod
Program d02pu_t2w_fe
! D02PU_T2W_F Example Main Program
! .. Use Statements ..
Use d02pu_t2w_fe_mod, Only: f, liwsav, lrwsav, n, nin, nout
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: d02pe_t2w_f, d02pq_t2w_f, d02pt_t2w_f, &
d02pu_t2w_f, nagad_t2w_w_rtype, sqrt, &
x10aa_t2w_f, x10ab_t2w_f, Assignment (=), &
Operator (-), Operator (/), Operator (+)
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Type (c_ptr) :: ad_handle
Type (nagad_t2w_w_rtype) :: eps, errmax, hnext, hs, te, terrmx, &
tgot, tol, ts, twant, waste
Real (Kind=nag_wp) :: epsr, hstart, t, tend, tolr, tstart
Integer :: fevals, ifail, method, stepcost, &
stepsok
! .. Local Arrays ..
Type (nagad_t2w_w_rtype) :: rmserr(n), ruser(1), th(n), y(n), &
ygot(n), ymax(n), ypgot(n)
Type (nagad_t2w_w_rtype), Allocatable :: rwsav(:)
Real (Kind=nag_wp) :: thresh(n), yr(n)
Integer :: iuser(1)
Integer, Allocatable :: iwsav(:)
! .. Executable Statements ..
Write (nout,*) 'D02PU_T2W_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,*) epsr
Read (nin,*) hstart, tolr
Read (nin,*) thresh(1:n)
! Set control for output
ts = tstart
te = tend
eps = epsr
tol = tolr
th(1:n) = thresh(1:n)
hs = hstart
! Create AD configuration data object
ifail = 0
Call x10aa_t2w_f(ad_handle,ifail)
eps%value%tangent = 1.0_nag_wp
eps%tangent%value = 1.0_nag_wp
y(1) = 1.0_nag_wp - eps
y(2) = 0.0_nag_wp
y(3) = 0.0_nag_wp
y(4) = sqrt((1.0_nag_wp+eps)/(1.0_nag_wp-eps))
Write (nout,99999) tolr
Write (nout,99998)
Write (nout,99997) tstart, y(1:n)%value
99999 Format (/,' Calculation with TOL = ',1P,E8.1)
99998 Format (/,' t y1 y2 y3 y4',/)
99997 Format (1X,F6.3,4(3X,F8.4))
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 0
Call d02pq_t2w_f(ad_handle,n,ts,te,y,tol,th,method,hs,iwsav,rwsav,ifail)
twant = te
integ: Do
ifail = -1
Call d02pe_t2w_f(ad_handle,f,n,twant,tgot,ygot,ypgot,ymax,iuser,ruser, &
iwsav,rwsav,ifail)
If (ifail<2 .Or. ifail>4) Then
Exit integ
End If
End Do integ
If (ifail==0) Then
t = tgot%value%value
yr(1:n) = ygot(1:n)%value%value
Write (nout,99997) t, yr(1:n)
! Get error estimates
ifail = 0
Call d02pu_t2w_f(ad_handle,n,rmserr,errmax,terrmx,iwsav,rwsav,ifail)
Write (nout,99996) rmserr(1:n)%value%value
Write (nout,99995) errmax%value%value, terrmx%value%value
ifail = 0
Call d02pt_t2w_f(ad_handle,fevals,stepcost,waste,stepsok,hnext,iwsav, &
rwsav,ifail)
Write (nout,99994) fevals
End If
99996 Format (/,' Componentwise error assessment',/,9X,4(2X,E9.2))
99995 Format (/,' Worst global error observed was ',E9.2, &
' - it occurred at T = ',F6.3)
99994 Format (/,' Cost of the integration in evaluations of F is',I6)
epsr = ygot(1)%tangent%tangent
Write (nout,*)
Write (nout,*) ' Derivatives calculated: Second order tangents'
Write (nout,*) ' Computational mode : algorithmic'
Write (nout,*)
Write (nout,*) ' Derivatives:'
Write (nout,99993) ' d^2y(t)/deps^2 =', epsr
99993 Format (1X,A,1X,E12.5)
! Remove computational data object
ifail = 0
Call x10ab_t2w_f(ad_handle,ifail)
End Program d02pu_t2w_fe