Program s17alfe
! S17ALF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: nag_wp, s17alf, x02ajf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: a, rel
Integer :: i, ifail, mode, n
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: x(:)
! .. Intrinsic Procedures ..
Intrinsic :: sqrt
! .. Executable Statements ..
Write (nout,*) 'S17ALF Example Program Results'
! Skip heading in data file
Read (nin,*)
rel = sqrt(x02ajf())
Read (nin,*) a, n, mode
Allocate (x(n))
ifail = 0
Call s17alf(a,n,mode,rel,x,ifail)
Write (nout,*)
Write (nout,*) ' A N MODE REL'
Write (nout,*) ' (machine-dependent)'
Write (nout,*)
Write (nout,99999) a, n, mode, rel
Write (nout,*)
Select Case (mode)
Case (1)
Write (nout,*) 'Leading N positive zeros of J'
Case (2)
Write (nout,*) 'Leading N positive zeros of Y'
Case (3)
If (a==0.0E0_nag_wp) Then
Write (nout,*) 'Leading N non-negative zeros of J'''
Else
Write (nout,*) 'Leading N positive zeros of J'''
End If
Case (4)
Write (nout,*) 'Leading N positive zeros of Y'''
End Select
Write (nout,*)
Write (nout,*) 'X ='
Write (nout,99998)(x(i),i=1,n)
Write (nout,*)
99999 Format (1X,F4.1,I4,I7,4X,1P,E9.1)
99998 Format (1P,(E12.4))
End Program s17alfe