Example description
    Program x10aa_a1w_fe

!     X10AA_A1W_F Example Program Text
!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: nagad_a1w_get_derivative,                       &
                               nagad_a1w_inc_derivative,                       &
                               nagad_a1w_ir_create,                            &
                               nagad_a1w_ir_interpret_adjoint,                 &
                               nagad_a1w_ir_register_variable,                 &
                               nagad_a1w_ir_remove, nagad_a1w_w_rtype,         &
                               nagad_algorithmic, nagad_symbolic, s01ba_a1w_f, &
                               x10aa_a1w_f, x10ab_a1w_f, x10ac_a1w_f,          &
                               x10ad_a1w_f, Assignment (=)
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nout = 6
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Type (nagad_a1w_w_rtype)         :: x, y
      Real (Kind=nag_wp)               :: dydx, dydx_exp, y1
      Integer                          :: ifail, mode
!     .. Executable Statements ..
      Write (nout,*) 'X10AA_A1W_F Example Program Results'

      x = 0.1_nag_wp

      Write (nout,*)
      Write (nout,*) 'Computing ln(1+x) and its adjoint using s01ba'

!     Create AD tape
      Call nagad_a1w_ir_create

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

!     Set computational mode to nagad_symbolic
      mode = nagad_symbolic
      ifail = 0
      Call x10ac_a1w_f(ad_handle,mode,ifail)

!     Get and print computational mode
!     Register variables to differentiate w.r.t.
      Write (nout,*)
      ifail = 0
      Call x10ad_a1w_f(ad_handle,mode,ifail)
      If (mode==nagad_symbolic) Then
        Write (nout,*) 'Symbolic computational mode is being used'
      Else If (mode==nagad_algorithmic) Then
        Write (nout,*) 'Algorithmic computational mode is being used'
      End If
      Write (nout,*)

!     Try AD computation that expects to use only the algorithmic mode
      ifail = 1
      Call s01ba_a1w_f(ad_handle,x,y,ifail)
      If (ifail==-199) Then
        Write (nout,99999) 'AD computation failed as expected with ifail = ',  &
          ifail
      Else
        Write (nout,*) ' Unexpected IFAIL returned in AD computation'
        Write (nout,99999) '   Ifail expected: ', -199
        Write (nout,99999) '   Ifail returned: ', ifail
        Go To 100
      End If
99999 Format (1X,A,I4)

      Write (nout,*)
!     Reset computational mode to nagad_algorithmic
      mode = nagad_algorithmic
      ifail = 0
      Call x10ac_a1w_f(ad_handle,mode,ifail)
      ifail = 0
      Call x10ad_a1w_f(ad_handle,mode,ifail)
      If (mode==nagad_symbolic) Then
        Write (nout,*) 'Symbolic computational mode is being used'
      Else If (mode==nagad_algorithmic) Then
        Write (nout,*) 'Algorithmic computational mode is being used'
      End If
      Write (nout,*)

      Call nagad_a1w_ir_register_variable(x)

      ifail = 0
      Call s01ba_a1w_f(ad_handle,x,y,ifail)
      y1 = y%value

      Call nagad_a1w_inc_derivative(y,1.0_nag_wp)
      ifail = 0
      Call nagad_a1w_ir_interpret_adjoint(ifail)

!     Get derivatives
      dydx = nagad_a1w_get_derivative(x)
      dydx_exp = 1.0_nag_wp/(1.0_nag_wp+x%value)

      Write (nout,99998) 'Input value of x             : ', x%value
      Write (nout,99998) 'Output value of ln(1+x)      : ', y1
      Write (nout,99998) 'AD evaluated derivative      : ', dydx
      Write (nout,99998) 'Directly computed derivative : ', dydx_exp
99998 Format (1X,A,1P,E11.3)

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

    End Program x10aa_a1w_fe