PROGRAM g08ecfe

!      G08ECF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. 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 20
          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

20     CONTINUE

99999  FORMAT (1X,A,I2)
99998  FORMAT (1X,A,F8.2)
99997  FORMAT (1X,A,F10.4)
    END PROGRAM g08ecfe