! D01AHF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
Module d01ahfe_mod
! D01AHF Example Program Module:
! Parameters and User-defined Routines
! .. Use Statements ..
Use nag_library, Only: nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Accessibility Statements ..
Private
Public :: f
! .. Parameters ..
Integer, Parameter, Public :: nin = 5, nout = 6
Contains
Function f(x)
! .. Function Return Value ..
Real (Kind=nag_wp) :: f
! .. Scalar Arguments ..
Real (Kind=nag_wp), Intent (In) :: x
! .. Executable Statements ..
f = 4.0E0_nag_wp/(1.0E0_nag_wp+x*x)
Return
End Function f
End Module d01ahfe_mod
Program d01ahfe
! D01AHF Example Main Program
! .. Use Statements ..
Use d01ahfe_mod, Only: f, nin, nout
Use nag_library, Only: d01ahf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Local Scalars ..
Real (Kind=nag_wp) :: a, ans, b, epsr, relerr
Integer :: ifail, nlimit, npts
! .. Executable Statements ..
Write (nout,*) 'D01AHF Example Program Results'
Read (nin,*)
Read (nin,*) a, b
Read (nin,*) nlimit
Read (nin,*) epsr
ifail = -1
ans = d01ahf(a,b,epsr,npts,relerr,f,nlimit,ifail)
Select Case (ifail)
Case (0:2)
Write (nout,*)
Write (nout,99999) 'Integral = ', ans
Write (nout,*)
Write (nout,99998) 'Estimated relative error = ', relerr
Write (nout,*)
Write (nout,99997) 'Number of function evaluations = ', npts
End Select
99999 Format (1X,A,F8.5)
99998 Format (1X,A,E10.2)
99997 Format (1X,A,I5)
End Program d01ahfe