Program g07gbfe
! G07GBF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: g07gbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: e, lx, ux, var1, var2, x
Integer :: ifail, n
Logical :: outlier
! .. Executable Statements ..
Write (nout,*) 'G07GBF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
d_lp: Do
! Read in the sample size, variances and value to test
Read (nin,*,Iostat=ifail) n, e, var1, var2
If (ifail/=0) Then
Exit d_lp
End If
! Check whether E is a potential outlier
ifail = 0
outlier = g07gbf(n,e,var1,var2,x,lx,ux,ifail)
! Display results
Write (nout,99999) 'Sample size :', n
Write (nout,99998) 'Largest absolute residual (E) :', e
Write (nout,99998) 'Variance for whole sample :', var1
Write (nout,99998) 'Variance excluding E :', var2
Write (nout,99998) 'Estimate for cutoff (X) :', x
Write (nout,99998) 'Lower limit for cutoff (LX) :', lx
Write (nout,99998) 'Upper limit for cutoff (UX) :', ux
If (outlier) Then
Write (nout,*) 'E is a potential outlier'
Else
Write (nout,*) 'E does not appear to be an outlier'
End If
Write (nout,*)
End Do d_lp
99999 Format (1X,A,1X,I10)
99998 Format (1X,A,1X,F10.3)
End Program g07gbfe