! E02DE_A1W_F Example Program Text
! Mark 30.1 Release. NAG Copyright 2024.
Program e02de_a1w_fe
! .. Use Statements ..
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: e01da_a1w_f, e02de_a1w_f, &
nagad_a1w_get_derivative, &
nagad_a1w_inc_derivative, &
nagad_a1w_ir_create => x10za_a1w_f, &
nagad_a1w_ir_interpret_adjoint_sparse, &
nagad_a1w_ir_register_variable, &
nagad_a1w_ir_remove, nagad_a1w_w_rtype, &
x10aa_a1w_f, x10ab_a1w_f, Assignment (=)
Use nag_library, Only: nag_wp, x04caf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Type (c_ptr) :: ad_handle
Integer :: ifail, j, m, mx, my, px, py
! .. Local Arrays ..
Type (nagad_a1w_w_rtype), Allocatable :: c(:), f(:,:), lamda(:), mu(:), &
wrk(:), x(:), y(:)
Type (nagad_a1w_w_rtype) :: ff(1), tx(1), ty(1)
Real (Kind=nag_wp), Allocatable :: df(:,:), xr(:), yr(:)
Integer, Allocatable :: iwrk(:)
! .. Executable Statements ..
Write (nout,*) 'E02DE_A1W_F Example Program Results'
! Skip heading in data file
Read (nin,*)
! Read the number of X points, MX, and the values of the
! X co-ordinates.
Read (nin,*) mx
Allocate (x(mx),xr(mx),lamda(mx+4))
Read (nin,*) xr(1:mx)
x(1:mx) = xr(1:mx)
! Read the number of Y points, MY, and the values of the
! Y co-ordinates.
Read (nin,*) my
Allocate (y(my),yr(my),mu(my+4),c(mx*my),f(my,mx),wrk((mx+6)*(my+6)))
Read (nin,*) yr(1:my)
y(1:my) = yr(1:my)
! Read the function values at the grid points.
Do j = 1, my
Read (nin,*) xr(1:mx)
f(j,1:mx) = xr(1:mx)
End Do
! Create AD tape
Call nagad_a1w_ir_create
! Create AD configuration data object and set computational mode
ifail = 0
Call x10aa_a1w_f(ad_handle,ifail)
ifail = 0
! Register variables to differentiate w.r.t.
Call nagad_a1w_ir_register_variable(x)
Call nagad_a1w_ir_register_variable(y)
Call nagad_a1w_ir_register_variable(f)
! Call AD Interpolating Function routine
ifail = 0
Call e01da_a1w_f(ad_handle,mx,my,x,y,f,px,py,lamda,mu,c,wrk,ifail)
Deallocate (wrk)
! Interpolant to be evaluated at a single point
m = 1
tx(1) = 1.4_nag_wp
ty(1) = 0.5_nag_wp
Allocate (wrk(py-4),iwrk(py-4))
ifail = 0
Call e02de_a1w_f(ad_handle,m,px,py,tx,ty,lamda,mu,c,ff,wrk,iwrk,ifail)
Write (nout,*)
Write (nout,99999) tx(1)%value, ty(1)%value
Write (nout,99998) ff(1)%value
99999 Format (1X,' Spline fitted at point x = ',F6.2,' and y = ',F6.2)
99998 Format (1X,' Value of fitted spline = ',F7.3)
! Setup evaluation of derivatives via adjoints
Call nagad_a1w_inc_derivative(ff(1),1.0_nag_wp)
ifail = 0
Call nagad_a1w_ir_interpret_adjoint_sparse(ifail)
Write (nout,*)
Write (nout,*) ' Derivatives calculated: First order adjoints'
Write (nout,*) ' Computational mode : algorithmic'
! Get derivatives
xr(1:mx) = nagad_a1w_get_derivative(x)
yr(1:my) = nagad_a1w_get_derivative(y)
Allocate (df(my,mx))
df(1:my,1:mx) = nagad_a1w_get_derivative(f)
Write (nout,*)
Write (nout,*) ' Derivatives of fitted value w.r.t. data points:'
Write (nout,*)
Call x04caf('General',' ',1,mx,xr,1,' dfit/dx ',ifail)
Write (nout,*)
Call x04caf('General',' ',1,my,yr,1,' dfit/dy ',ifail)
Write (nout,*)
Write (nout,*) ' Derivatives of fitted value w.r.t. f-values:'
Write (nout,*)
Call x04caf('General',' ',my,mx,df,my,' dfit/df ',ifail)
! Remove computational data object and tape
Call x10ab_a1w_f(ad_handle,ifail)
Call nagad_a1w_ir_remove
End Program e02de_a1w_fe