Example description
    Program g08edfe

!     G08EDF Example Program Text

!     Mark 27.1 Release. NAG Copyright 2020.

!     .. Use Statements ..
      Use nag_library, Only: g08edf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: chi, df, prob, rlo, rup, totlen
      Integer                          :: i, ifail, m, maxg, n, ngaps, nsamp,  &
                                          pn
      Character (1)                    :: cl
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: ex(:), x(:)
      Integer, Allocatable             :: ncount(:)
!     .. Executable Statements ..
      Write (nout,*) 'G08EDF Example Program Results'
      Write (nout,*)

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

!     Read in number of samples and control parameters
      Read (nin,*) nsamp, m, maxg
      Read (nin,*) rlo, rup, totlen

      Allocate (ncount(maxg),ex(maxg),x(1))

      If (nsamp==1) Then
        cl = 'S'
      Else
        cl = 'F'
      End If

      pn = 0
      Do i = 1, nsamp
!       Skip run heading in data file
        Read (nin,*)

!       Read in sample size
        Read (nin,*) n

        If (n>pn) Then
!         Reallocate X if required
          Deallocate (x)
          Allocate (x(n))
          pn = n
        End If

!       Read in the sample
        Read (nin,*) x(1:n)

!       Process the sample
        ifail = -1
        Call g08edf(cl,n,x,m,maxg,rlo,rup,totlen,ngaps,ncount,ex,chi,df,prob,  &
          ifail)
        If (ifail/=0 .And. ifail<8) Then
          Go To 100
        End If

!       Adjust CL for intermediate calls
        If (i<nsamp-1) Then
          cl = 'I'
        Else
          cl = 'L'
        End If

      End Do

!     Display results
      Write (nout,99999) 'Total number of gaps found = ', ngaps
      If (ifail==8) Then
        Write (nout,*)                                                         &
          ' ** Note : the number of gaps requested were not found.'
      End If
      Write (nout,*)
      Write (nout,*) 'Count'
      Write (nout,*)                                                           &
        '      0      1      2      3      4      5      6      7      8',     &
        '     >9'
      Write (nout,99998) ncount(1:maxg)
      Write (nout,*)
      Write (nout,*) 'Expect'
      Write (nout,*)                                                           &
        '      0      1      2      3      4      5      6      7      8',     &
        '     >9'
      Write (nout,99997) ex(1:maxg)
      Write (nout,*)
      Write (nout,99996) 'Chisq = ', chi
      Write (nout,99995) 'DF    = ', df
      Write (nout,99996) 'Prob  = ', prob
      If (ifail==9) Then
        Write (nout,*) ' ** Note : expected value <= 5.0'
        Write (nout,*)                                                         &
          '    the chi square approximation may not be very good.'
      End If

100   Continue

99999 Format (1X,A,I10)
99998 Format (1X,10I7)
99997 Format (1X,10F7.1)
99996 Format (1X,A,F10.4)
99995 Format (1X,A,F7.1)
    End Program g08edfe