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

NAG AD Library Introduction
Example description
!   D01UA_P0W_F Example Program Text
!   Mark 27.3 Release. NAG Copyright 2021.

    Module d01ua_p0w_fe_mod

!     .. Use Statements ..
      Use iso_c_binding, Only: c_ptr
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Accessibility Statements ..
      Private
      Public                           :: f
!     .. Parameters ..
      Integer, Parameter, Public       :: nout = 6
    Contains
      Subroutine f(ad_handle,x,nx,fv,iflag,iuser,ruser)

!       .. Scalar Arguments ..
        Type (c_ptr), Intent (Inout)   :: ad_handle
        Integer, Intent (Inout)        :: iflag
        Integer, Intent (In)           :: nx
!       .. Array Arguments ..
        Real (Kind=nag_wp), Intent (Out) :: fv(nx)
        Real (Kind=nag_wp), Intent (Inout) :: ruser(*)
        Real (Kind=nag_wp), Intent (In) :: x(nx)
        Integer, Intent (Inout)        :: iuser(*)
!       .. Intrinsic Procedures ..
        Intrinsic                      :: exp, log
!       .. Executable Statements ..
        Select Case (iuser(1))
        Case (1)
          fv = 4.0E0_nag_wp/(1.0E0_nag_wp+ruser(1)*x*x)
        Case (2)
          fv = 1.0E0_nag_wp/(x*x*log(ruser(1)*x))
        Case (3)
          fv = exp(-ruser(1)*x)/x
        Case (4)
          fv = ruser(1)/x
        Case (5)
          fv = exp(-3.0E0_nag_wp*ruser(1)*x*x-4.0E0_nag_wp*x-1.0E0_nag_wp)
        Case (6)
          fv = exp(2.0E0_nag_wp*ruser(1)*x+2.0E0_nag_wp)
        Case Default
          iflag = -1
        End Select
        Return
      End Subroutine f
    End Module d01ua_p0w_fe_mod

    Program d01ua_p0w_fe
!     D01UA_P0W_F Example Main Program

!     .. Use Statements ..
      Use d01ua_p0w_fe_mod, Only: f, nout
      Use iso_c_binding, Only: c_ptr
      Use nagad_library, Only: d01ua_p0w_f
      Use nag_library, Only: nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Local Scalars ..
      Type (c_ptr)                     :: ad_handle
      Real (Kind=nag_wp)               :: a, b, dinest
      Integer                          :: funid, ifail, key, n
!     .. Local Arrays ..
      Real (Kind=nag_wp)               :: ruser(1)
      Integer                          :: iuser(1)
!     .. Executable Statements ..

      Write (nout,*) 'D01UA_P0W_F Example Program Results'

      n = 64
      ruser(1) = 1.0_nag_wp

cases: Do funid = 1, 6
        Write (nout,*)
        Select Case (funid)
        Case (1)
          Write (nout,*) 'Gauss-Legendre example'
          a = 0.0_nag_wp
          b = 1.0_nag_wp
          key = 0
        Case (2)
          Write (nout,*) 'Rational Gauss example'
          a = 2.0_nag_wp
          b = 0.0_nag_wp
          key = -5
        Case (3)
          Write (nout,*) 'Gauss-Laguerre example (adjusted weights)'
          a = 2.0_nag_wp
          b = 1.0_nag_wp
          key = -3
        Case (4)
          Write (nout,*) 'Gauss-Laguerre example (normal weights)'
          a = 2.0_nag_wp
          b = 1.0_nag_wp
          key = 3
        Case (5)
          Write (nout,*) 'Gauss-Hermite example (adjusted weights)'
          a = -1.0_nag_wp
          b = 3.0_nag_wp
          key = -4
        Case (6)
          Write (nout,*) 'Gauss-Hermite example (normal weights)'
          a = -1.0_nag_wp
          b = 3.0_nag_wp
          key = 4
        End Select
        iuser(1) = funid

!       Call the passive routine
        ifail = 0
        Call d01ua_p0w_f(ad_handle,key,a,b,n,f,dinest,iuser,ruser,ifail)

        Write (nout,*)
        Write (nout,99999) 'dinest   =', dinest
99999   Format (1X,A,1X,F10.5)

      End Do cases

    End Program d01ua_p0w_fe