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

NAG AD Library Introduction
Example description
    Program f07ca_a1t1w_fe

!     F07CA_A1T1W_F Example Program Text
!     Mark 28.5 Release. NAG Copyright 2022.

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: f07ca_a1t1w_f, nagad_a1t1w_get_derivative,      &
                               nagad_a1t1w_inc_derivative,                     &
                               nagad_a1t1w_ir_create => x10za_a1t1w_f,         &
                               nagad_a1t1w_ir_interpret_adjoint,               &
                               nagad_a1t1w_ir_register_variable,               &
                               nagad_a1t1w_ir_remove, nagad_a1t1w_w_rtype,     &
                               nagad_symbolic, nagad_t1w_w_rtype,              &
                               x10aa_a1t1w_f, x10ab_a1t1w_f, x10ac_a1t1w_f,    &
                               Assignment (=)
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6, nrhs = 1
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Type (nagad_t1w_w_rtype)         :: t_t
      Real (Kind=nag_wp)               :: dx
      Integer                          :: i, ifail, mode, n
!     .. Local Arrays ..
      Type (nagad_a1t1w_w_rtype), Allocatable :: b(:), d(:), df(:), dl(:),     &
                                          dlf(:), du(:), duf(:), x(:)
      Real (Kind=nag_wp), Allocatable  :: dxdb(:), dxdd(:), dxddl(:), dxddu(:)
!     .. Executable Statements ..
      Write (nout,*) 'F07CA_A1T1W_F Example Program Results'
      Write (nout,*)
!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n
      Read (nin,*) mode

      Allocate (b(n),d(n),dl(n-1),du(n-1))
      Allocate (x(n),df(n),dlf(n-1),duf(n-1))
      Allocate (dxdb(n),dxdd(n),dxddl(n-1),dxddu(n-1))

!     Read the tridiagonal matrix A and the right hand side B from
!     data file and initialize AD arrays

      Read (nin,*) dxddu(1:n-1)
      Read (nin,*) dxdd(1:n)
      Read (nin,*) dxddl(1:n-1)
      Read (nin,*) dxdb(1:n)
      du(1:n-1) = dxddu(1:n-1)
      d(1:n) = dxdd(1:n)
      dl(1:n-1) = dxddl(1:n-1)
      b(1:n) = dxdb(1:n)

!     Create AD tape
      Call nagad_a1t1w_ir_create

!     Create AD configuration data object
      ifail = 0
      Call x10aa_a1t1w_f(ad_handle,ifail)

!     Set AD computational mode
      ifail = 0
      Call x10ac_a1t1w_f(ad_handle,mode,ifail)

!     Register variables to differentiate w.r.t.
      dl(1:n-1)%value%tangent = 1.0_nag_wp
      d(1:n)%value%tangent = 1.0_nag_wp
      du(1:n-1)%value%tangent = 1.0_nag_wp
      b(1:n)%value%tangent = 1.0_nag_wp
      Call nagad_a1t1w_ir_register_variable(dl)
      Call nagad_a1t1w_ir_register_variable(d)
      Call nagad_a1t1w_ir_register_variable(du)
      Call nagad_a1t1w_ir_register_variable(b)

      dlf = dl
      df = d
      duf = du
      x = b

!     Solve the equations Ax = b for x

!     The NAG name equivalent of dgtsv_a1t1w is f07ca_a1t1w_f
      ifail = 0
      Call f07ca_a1t1w_f(ad_handle,n,nrhs,dlf,df,duf,x,n,ifail)

      If (ifail==0) Then

!       Print primal solution

        Write (nout,*) 'Solution'
        Write (nout,99999) x(1:n)%value%value

      Else
        Write (nout,99998) 'Element U(', ifail, ',', ifail, ') is zero'
        Go To 100
      End If

99999 Format ((1X,7F11.4))
99998 Format (1X,A,I0,A,I0,A)

      Write (nout,*)
      Write (nout,*)                                                           &
        ' Derivatives calculated: Second order, adjoints of tangents'
      If (mode==nagad_symbolic) Then
        Write (nout,*) ' Computational mode    : symbolic'
      Else
        Write (nout,*) ' Computational mode    : algorithmic'
      End If

      Write (nout,*)
      Write (nout,*) ' Derivatives of solution w.r.t. inputs:'

!     Setup evaluation of derivatives via adjoints
      t_t = 1.0_nag_wp
      Call nagad_a1t1w_inc_derivative(x(1:n),t_t)
      ifail = 0
      Call nagad_a1t1w_ir_interpret_adjoint(ifail)

!       Get derivatives
      dx = 0.0_nag_wp
      Do i = 1, n - 1
        t_t = nagad_a1t1w_get_derivative(du(i))
        dx = dx + t_t%tangent
        t_t = nagad_a1t1w_get_derivative(dl(i))
        dx = dx + t_t%tangent
      End Do
      Do i = 1, n
        t_t = nagad_a1t1w_get_derivative(d(i))
        dx = dx + t_t%tangent
        t_t = nagad_a1t1w_get_derivative(b(i))
        dx = dx + t_t%tangent
      End Do
      Write (nout,*)
      Write (nout,'(1X,A)') 'Sum of Hessian terms for x w.r.t. du, d, dl, b '
      Write (nout,*)
      Write (nout,'(1X,A,E11.2)')                                              &
        'Sum_{i,j,k} d^2 x_k / d{A,b}_{i} d{A,b}_{j}: ', dx

!     Remove computational data object and tape
100   Continue
      Call x10ab_a1t1w_f(ad_handle,ifail)
      Call nagad_a1t1w_ir_remove


    End Program f07ca_a1t1w_fe