Example description
    Program g07abfe

!     G07ABF Example Program Text

!     Mark 26.2 Release. NAG Copyright 2017.

!     .. Use Statements ..
      Use nag_library, Only: g07abf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: clevel, sum_nag, tl, tu, xmean
      Integer                          :: ifail, ifreq, n, num
!     .. Intrinsic Procedures ..
      Intrinsic                        :: real
!     .. Executable Statements ..
      Write (nout,*) 'G07ABF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Read in counts and frequencies
      sum_nag = 0.0E0_nag_wp
      n = 0
d_lp: Do
        Read (nin,*,Iostat=ifail) num, ifreq
        If (ifail/=0) Then
          Exit d_lp
        End If

!       Calculate sum
        sum_nag = sum_nag + real(num,kind=nag_wp)*real(ifreq,kind=nag_wp)
        n = n + ifreq
      End Do d_lp

!     Estimate Poisson parameter
      xmean = sum_nag/real(n,kind=nag_wp)
      Write (nout,99999) 'The point estimate of the Poisson parameter =',      &
        xmean
      Write (nout,*)

!     Calculate 95% confidence interval
      clevel = 0.95E0_nag_wp
      ifail = 0
      Call g07abf(n,xmean,clevel,tl,tu,ifail)

!     Display CI
      Write (nout,*) '95 percent Confidence Interval for the estimate'
      Write (nout,99998) '(', tl, ' ,', tu, ' )'
      Write (nout,*)

!     Calculate 99% confidence interval
      clevel = 0.99E0_nag_wp
      ifail = 0
      Call g07abf(n,xmean,clevel,tl,tu,ifail)

!     Display CI
      Write (nout,*) '99 percent Confidence Interval for the estimate'
      Write (nout,99998) '(', tl, ' ,', tu, ' )'

99999 Format (1X,A,F7.4)
99998 Format (6X,A,F7.4,A,F7.4,A)
    End Program g07abfe