Program e02alfe
! E02ALF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: e02alf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: dxx, ref, s, t, xx
Integer :: i, ifail, j, m, n, neval
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: a(:), x(:), y(:)
! .. Intrinsic Procedures ..
Intrinsic :: exp, real
! .. Executable Statements ..
Write (nout,*) 'E02ALF Example Program Results'
! Skip heading in data file
Read (nin,*)
Read (nin,*) n, m, neval
Allocate (a(m+1),x(n),y(n))
Read (nin,*)(x(i),y(i),i=1,n)
ifail = 0
Call e02alf(n,x,y,m,a,ref,ifail)
Write (nout,*)
Write (nout,*) ' Polynomial coefficients'
Write (nout,99998)(a(i),i=1,m+1)
Write (nout,*)
Write (nout,99997) ' Reference deviation = ', ref
Write (nout,*)
Write (nout,*) ' x Fit exp(x) Residual'
! The neval evaluation points are equispaced on [0,1].
dxx = 1.0_nag_wp/real(neval-1,kind=nag_wp)
Do j = 1, neval
xx = real(j-1,kind=nag_wp)*dxx
s = a(m+1)
Do i = m, 1, -1
s = s*xx + a(i)
End Do
t = exp(xx)
Write (nout,99999) xx, 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 e02alfe