e02aefe.f90

 Program e02aefe
! E02AEF Example Program Text
! Mark 31.1 Release. nAG Copyright 2025.
! .. Use Statements ..
 Use nag_library, Only: e02aef, nag_wp
! .. Implicit None Statement ..
 Implicit None
! .. Parameters ..
 Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
 Real (Kind=nag_wp) :: p, xcap
 Integer :: i, ifail, m, n, nplus1, r
! .. Local Arrays ..
 Real (Kind=nag_wp), Allocatable :: a(:)
! .. Intrinsic Procedures ..
 Intrinsic :: real
! .. Executable Statements ..
 Write (nout,*) 'E02AEF Example Program Results'
! Skip heading in data file
 Read (nin,*)
 Read (nin,*) m
 Read (nin,*) n
 nplus1 = n + 1
 Allocate (a(nplus1))
 Read (nin,*)(a(i),i=1,nplus1)
 Do r = 1, m
 xcap = real(2*r-m-1,kind=nag_wp)/real(m-1,kind=nag_wp)
 ifail = 0
 Call e02aef(nplus1,a,xcap,p,ifail)
 If (r==1) Then
 Write (nout,*)
 Write (nout,*) ' R Argument Value of polynomial'
 End If
 Write (nout,99999) r, xcap, p
 End Do
99999 Format (1X,I3,F14.4,4X,F14.4)
 End Program e02aefe

AltStyle によって変換されたページ (->オリジナル) /