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

NAG AD Library Introduction
Example description
!   E01BA_T1W_F Example Program Text
!   Mark 28.5 Release. NAG Copyright 2022.
    Program e01ba_t1w_fe

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: e01ba_t1w_f, e02bb_t1w_f, exp,                  &
                               nagad_t1w_set_derivative, nagad_t1w_w_rtype,    &
                               x10aa_t1w_f, x10ab_t1w_f, Assignment (=)
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: m = 7, nout = 6
      Integer, Parameter               :: lck = m + 4
      Integer, Parameter               :: lwrk = 6*m + 16
      Real (Kind=nag_wp), Parameter    :: xc(m) = (/0.0_nag_wp,0.2_nag_wp,     &
                                          0.4_nag_wp,0.6_nag_wp,0.75_nag_wp,   &
                                          0.9_nag_wp,1.0_nag_wp/)
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Type (nagad_t1w_w_rtype)         :: fit, xint
      Integer                          :: i, ifail, j
!     .. Local Arrays ..
      Type (nagad_t1w_w_rtype)         :: c(lck), lamda(lck), wrk(lwrk), x(m), &
                                          y(m)
      Real (Kind=nag_wp)               :: dx(m), dy(m)
!     .. Executable Statements ..
      Write (nout,*) 'E01BA_T1W_F Example Program Results'

!     Create AD configuration data object and set computational mode
      ifail = 0
      Call x10aa_t1w_f(ad_handle,ifail)

      x(1:m) = xc(1:m)
      y(1:m) = exp(x(1:m))

      xint = 0.5_nag_wp
      Do i = 1, 2*m

        If (i<=m) Then
          Call nagad_t1w_set_derivative(x(i),1.0_nag_wp)
        Else
          Call nagad_t1w_set_derivative(y(i-m),1.0_nag_wp)
        End If

        c = 0.0_nag_wp

!       Call AD routine
        ifail = 0
        Call e01ba_t1w_f(ad_handle,m,x,y,lamda,c,lck,wrk,lwrk,ifail)

!       Call Use spline computed by e01ba to fit value at x = 0.5 using e02bb
        fit = 0.0_nag_wp
        ifail = 0
        Call e02bb_t1w_f(ad_handle,lck,lamda,c,xint,fit,ifail)

        If (i<=m) Then
          dx(i) = fit%tangent
          x(i)%tangent = 0.0_nag_wp
        Else
          dy(i-m) = fit%tangent
          y(i-m)%tangent = 0.0_nag_wp
        End If

      End Do

      Write (nout,*)
      Write (nout,99999) xint%value, fit%value
99999 Format (1X,' Value of fitted spline at x = ',F6.2,', is: ',F7.4)

      Write (nout,*)
      Write (nout,*) ' Derivatives calculated: First order tangents'
      Write (nout,*) ' Computational mode    : algorithmic'

      Write (nout,*)
      Write (nout,*) ' Derivatives of fitted value w.r.t. data points:'
      Write (nout,*) '  j    d/dx(j)      d/y(j)'
      Do j = 1, m
        Write (nout,99998) j, dx(j), dy(j)
      End Do
99998 Format (1X,I3,1X,E12.5,1X,E12.5)

!     Remove computational data object
      Call x10ab_t1w_f(ad_handle,ifail)

    End Program e01ba_t1w_fe