Program g08ecfe

!     G08ECF Example Program Text

!     Mark 25 Release. NAG Copyright 2014.

!     .. Use Statements ..
      Use nag_library, Only: g08ecf, nag_wp, x04eaf
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: chi, df, ex, prob
      Integer                          :: i, ifail, ldc, msize, n, nsamp, pn
      Logical                          :: bapp
      Character (1)                    :: cl
      Character (80)                   :: title
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: x(:)
      Integer, Allocatable             :: ncount(:,:,:)
!     .. Executable Statements ..
      Write (nout,*) 'G08ECF Example Program Results'
      Write (nout,*)

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

!     Read in number of samples
      Read (nin,*) nsamp, msize

      ldc = msize
      Allocate (ncount(ldc,ldc,msize),x(1))

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

      pn = 0
      bapp = .False.
      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 g08ecf(cl,n,x,msize,ncount,ldc,ex,chi,df,prob,ifail)
        If (ifail==7) Then
          bapp = .True.
        Else If (ifail/=0) 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,*) 'Count matrix'
      Do i = 1, msize
        Write (nout,*)
        Write (title,99999) 'I = ', i
        Flush (nout)
        ifail = 0
        Call x04eaf('General',' ',msize,msize,ncount(1,1,i),ldc,title,ifail)
      End Do
      Write (nout,*)
      Write (nout,99998) 'Expected value = ', ex
      Write (nout,99997) 'CHISQ          = ', chi
      Write (nout,99998) 'DF             = ', df
      Write (nout,99997) 'Prob           = ', prob
      If (bapp) 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,I2)
99998 Format (1X,A,F8.2)
99997 Format (1X,A,F10.4)
    End Program g08ecfe