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

NAG AD Library Introduction
Example description
!   E02BB_P0W_F Example Program Text
!   Mark 28.6 Release. NAG Copyright 2022.
    Program e02bb_p0w_fe

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: e01ba_p0w_f, e02bb_p0w_f
      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
      Real (Kind=nag_wp)               :: fit, xint
      Integer                          :: ifail
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: c(lck), lamda(lck), wrk(lwrk), x(m), &
                                          y(m)
!     .. Intrinsic Procedures ..
      Intrinsic                        :: exp
!     .. Executable Statements ..
      Write (nout,*) 'E02BB_P0W_F Example Program Results'

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

      c = 0.0_nag_wp

!     Call passive routine
      ifail = 0
      Call e01ba_p0w_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
      xint = 0.5_nag_wp
      ifail = 0
      Call e02bb_p0w_f(ad_handle,lck,lamda,c,xint,fit,ifail)
      Write (nout,*)
      Write (nout,99999) xint, fit
99999 Format (1X,' Value of fitted spline at x = ',F6.2,', is: ',F7.4)

    End Program e02bb_p0w_fe