Program f07ca_t2w_fe
! F07CA_T2W_F Example Program Text
! Mark 29.0 Release. NAG Copyright 2023.
! .. Use Statements ..
Use iso_c_binding, Only: c_ptr
Use nagad_library, Only: f07ca_t2w_f, nagad_t2w_w_rtype, x10aa_t1w_f, &
x10ab_t1w_f, Assignment (=)
Use nag_library, Only: nag_wp, x04caf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6, nrhs = 1
! .. Local Scalars ..
Type (c_ptr) :: ad_handle
Integer :: i, ifail, j, n
! .. Local Arrays ..
Type (nagad_t2w_w_rtype), Allocatable :: b(:), d(:), df(:), dl(:), &
dlf(:), du(:), duf(:), x(:)
Real (Kind=nag_wp), Allocatable :: dxdd(:,:,:)
! .. Executable Statements ..
Write (nout,*) 'F07CA_T2W_F Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
Read (nin,*) n
Allocate (b(n),d(n),dl(n-1),du(n-1))
Allocate (x(n),df(n),dlf(n-1),duf(n-1))
Allocate (dxdd(n,n,n))
! Read the tridiagonal matrix A and the right hand side B from
! data file and initialize AD arrays
Read (nin,*) dxdd(1:n-1,1,1)
du(1:n-1) = dxdd(1:n-1,1,1)
Read (nin,*) dxdd(1:n,1,1)
d(1:n) = dxdd(1:n,1,1)
Read (nin,*) dxdd(1:n-1,1,1)
dl(1:n-1) = dxdd(1:n-1,1,1)
Read (nin,*) dxdd(1:n,1,1)
b(1:n) = dxdd(1:n,1,1)
! Create AD configuration data object
ifail = 0
Call x10aa_t1w_f(ad_handle,ifail)
Do i = 1, n
d(i)%value%tangent = 1.0_nag_wp
Do j = 1, n
d(j)%tangent%value = 1.0_nag_wp
dlf = dl
df = d
duf = du
x = b
! Solve the equations Ax = b for x
ifail = 0
Call f07ca_t2w_f(ad_handle,n,nrhs,dlf,df,duf,x,n,ifail)
d(j)%tangent%value = 0.0_nag_wp
dxdd(i,j,1:n) = x(1:n)%tangent%tangent
End Do
d(i)%value%tangent = 0.0_nag_wp
End Do
! Print primal solution
Write (nout,*) 'Solution'
Write (nout,99999) x(1:n)%value%value
99999 Format (1X,7F11.4)
Write (nout,*)
Write (nout,*) ' Derivatives calculated: Second order tangents'
Write (nout,*) ' Computational mode : algorithmic'
Write (nout,*)
Write (nout,*) ' Derivatives of solution w.r.t. input vector d'
Write (nout,*)
Do i = 1, n
Write (nout,*)
Write (nout,'(2X,A,I0)') ' Derivatives for solution point i = ', i
Write (nout,*)
Call x04caf('General',' ',n,n,dxdd(1,1,i),n,'d^2(x_i)/d(d_j)d(d_k)', &
ifail)
End Do
! Remove computational data object
Call x10ab_t1w_f(ad_handle,ifail)
End Program f07ca_t2w_fe