Program e02acfe
! E02ACF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: e02acf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: m1 = 6, n = 21, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: ref, s, t, z
Integer :: i, j
! .. Local Arrays ..
Real (Kind=nag_wp) :: a(m1), x(n), y(n)
! .. Intrinsic Procedures ..
Intrinsic :: exp, real
! .. Executable Statements ..
Write (nout,*) 'E02ACF Example Program Results'
x(1:n) = real((/(i-1,i=1,n)/),kind=nag_wp)/real(n-1,kind=nag_wp)
y(1:n) = exp(x(1:n))
Call e02acf(x,y,n,a,m1,ref)
Write (nout,*)
Write (nout,*) ' Polynomial coefficients'
Write (nout,99998)(a(i),i=1,m1)
Write (nout,*)
Write (nout,99997) ' Reference deviation = ', ref
Write (nout,*)
Write (nout,*) ' X exp(X) Fit Residual'
Do j = 1, n, 2
z = x(j)
s = a(m1)
Do i = m1 - 1, 1, -1
s = s*z + a(i)
End Do
t = y(j)
Write (nout,99999) z, s, t, s - t
End Do
99999 Format (1X,F5.2,2F9.4,E11.2)
99998 Format (6X,E12.4)
99997 Format (1X,A,E10.2)
End Program e02acfe