Program e02ahfe
! E02AHF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: e02ahf, e02akf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Real (Kind=nag_wp), Parameter :: xmax = 2.5E0_nag_wp
Real (Kind=nag_wp), Parameter :: xmin = -0.5E0_nag_wp
Integer, Parameter :: nout = 6, np1 = 7
Integer, Parameter :: la = np1
Integer, Parameter :: ladif = np1
Real (Kind=nag_wp), Parameter :: a(la) = (/2.53213E0_nag_wp, &
1.13032E0_nag_wp,0.27150E0_nag_wp,0.04434E0_nag_wp,0.00547E0_nag_wp, &
0.00054E0_nag_wp,0.00004E0_nag_wp/)
! .. Local Scalars ..
Real (Kind=nag_wp) :: deriv, deriv2, patm1, x
Integer :: i, ifail, m
! .. Local Arrays ..
Real (Kind=nag_wp) :: adif(ladif), adif2(ladif)
! .. Intrinsic Procedures ..
Intrinsic :: real
! .. Executable Statements ..
Write (nout,*) 'E02AHF Example Program Results'
ifail = 0
Call e02ahf(np1,xmin,xmax,a,1,la,patm1,adif,1,ladif,ifail)
ifail = 0
Call e02ahf(np1-1,xmin,xmax,adif,1,ladif,patm1,adif2,1,ladif,ifail)
m = 4
Write (nout,*)
Write (nout,*) ' I Argument 1st deriv 2nd deriv'
Do i = 1, m
x = (xmin*real(m-i,kind=nag_wp)+xmax*real(i-1,kind=nag_wp))/ &
real(m-1,kind=nag_wp)
ifail = 0
Call e02akf(np1-1,xmin,xmax,adif,1,ladif,x,deriv,ifail)
ifail = 0
Call e02akf(np1-2,xmin,xmax,adif2,1,ladif,x,deriv2,ifail)
Write (nout,99999) i, x, deriv, deriv2
End Do
99999 Format (1X,I4,F9.4,2(4X,F9.4))
End Program e02ahfe