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

NAG AD Library Introduction
Example description
    Program g02da_a1w_fe

!     G02DA_A1W_F Example Program Text
!     Mark 27.3 Release. NAG Copyright 2021.

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: g02da_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_ir_zero_adjoints &
                               , 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
      Type (nagad_a1w_w_rtype)         :: rss, tol
      Integer                          :: i, idf, ifail, ip, irank, ldq, ldx,  &
                                          lwt, m, n
      Logical                          :: svd
      Character (1)                    :: mean, weight
!     .. Local Arrays ..
      Type (nagad_a1w_w_rtype), Allocatable :: b(:), cov(:), h(:), p(:),       &
                                          q(:,:), res(:), se(:), wk(:), wt(:), &
                                          x(:,:), y(:)
      Real (Kind=nag_wp), Allocatable  :: dbdy(:,:), dy(:)
      Integer, Allocatable             :: isx(:)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: count
!     .. Executable Statements ..
      Write (nout,*) 'G02DA_A1W_F Example Program Results'
      Flush (nout)

!     Skip heading in data file
      Read (nin,*)
      Read (nin,*) n, m, weight, mean

      If (weight=='W' .Or. weight=='w') Then
        lwt = n
      Else
        lwt = 0
      End If
      ldx = n
      Allocate (x(ldx,m),y(n),wt(lwt),isx(m),dy(n))

!     Read in data
      x(1:n,1:m) = 0.0_nag_wp
      y(1:n) = 0.0_nag_wp
      wt(1:lwt) = 0.0_nag_wp
      If (lwt>0) Then
        Read (nin,*)(x(i,1:m)%value,y(i)%value,wt(i)%value,i=1,n)
      Else
        Read (nin,*)(x(i,1:m)%value,y(i)%value,i=1,n)
      End If

!     Read in variable inclusion flags
      Read (nin,*) isx(1:m)

!     Calculate IP
      ip = count(isx(1:m)>0)
      If (mean=='M' .Or. mean=='m') Then
        ip = ip + 1
      End If

      ldq = n

      Allocate (b(ip),cov((ip*ip+ip)/2),h(n),p(ip*(ip+                         &
        2)),q(ldq,ip+1),res(n),se(ip),wk(ip*ip+5*(ip-1)),dbdy(n,ip))

!     Use suggested value for tolerance
      tol = 0.000001E0_nag_wp

!     Create AD tape
      Call nagad_a1w_ir_create

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

!     Register variables to differentiate w.r.t.
      Call nagad_a1w_ir_register_variable(y)

!     Fit general linear regression model
      ifail = -1
      Call g02da_a1w_f(ad_handle,mean,weight,n,x,ldx,m,isx,ip,y,wt,rss,idf,b,  &
        se,cov,res,h,q,ldq,svd,irank,p,tol,wk,ifail)
      If (ifail/=0) Then
        If (ifail/=5) Then
          Go To 100
        End If
      End If

!     Display results
      If (svd) Then
        Write (nout,99999) 'Model not of full rank, rank = ', irank
        Write (nout,*)
      End If
      Write (nout,99998) 'Residual sum of squares = ', rss%value
      Write (nout,99999) 'Degrees of freedom      = ', idf
      Write (nout,*)
      Write (nout,*) 'Variable   Parameter estimate   Standard error'
      Write (nout,*)
      If (ifail==0) Then
        Write (nout,99997)(i,b(i)%value,se(i)%value,i=1,ip)
      Else
        Write (nout,99996)(i,b(i)%value,i=1,ip)
      End If

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

      Write (nout,*)
      Write (nout,*) ' Derivatives:'
      Write (nout,*)

!     Setup evaluation of derivatives via adjoints
      Call nagad_a1w_inc_derivative(rss,1.0_nag_wp)
      ifail = 0
      Call nagad_a1w_ir_interpret_adjoint_sparse(ifail)

!     Get derivatives
      dy(1:n) = nagad_a1w_get_derivative(y)
      Write (nout,*) '    i        d(rss)/dy(i) '
      Do i = 1, n
        Write (nout,99995) i, dy(i)
      End Do

!     Setup evaluation of other derivatives via adjoints
      Do i = 1, ip
        Call nagad_a1w_ir_zero_adjoints
        Call nagad_a1w_inc_derivative(b(i),1.0_nag_wp)
        ifail = 0
        Call nagad_a1w_ir_interpret_adjoint_sparse(ifail)

        dbdy(1:n,i) = nagad_a1w_get_derivative(y(1:n))
      End Do

      Write (nout,*)
      ifail = 0
      Call x04caf('General',' ',n,ip,dbdy,n,'    db/dy',ifail)

100   Continue
!     Remove computational data object and tape
      Call x10ab_a1w_f(ad_handle,ifail)
      Call nagad_a1w_ir_remove

99999 Format (1X,A,I4)
99998 Format (1X,A,E12.4)
99997 Format (1X,I6,2E20.4)
99996 Format (1X,I6,E20.4)
99995 Format (1X,I5,6X,F9.4)
    End Program g02da_a1w_fe