PROGRAM g08eafe ! G08EAF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g08eaf, nag_wp, x04caf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: chi, df, prob INTEGER :: i, ifail, ldcov, lwrk, m, maxr, n, & nruns, nsamp, pn CHARACTER (1) :: cl ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: cov(:,:), ex(:), wrk(:), x(:) INTEGER, ALLOCATABLE :: ncount(:) ! .. Executable Statements .. WRITE (nout,*) 'G08EAF Example Program Results' WRITE (nout,*) ! Skip main heading in data file READ (nin,*) ! Read in number of samples READ (nin,*) nsamp, m, maxr ldcov = maxr lwrk = maxr*(maxr+5)/2 + 1 ALLOCATE (ncount(maxr),cov(ldcov,maxr),ex(maxr),wrk(lwrk),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 g08eaf(cl,n,x,m,maxr,nruns,ncount,ex,cov,ldcov,chi,df,prob,wrk, & lwrk,ifail) IF (ifail/=0 .AND. ifail/=10) 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,99999) 'Total number of runs found = ', nruns IF (ifail==10) THEN WRITE (nout,*) & ' ** Note : the number of runs requested were not found.' END IF WRITE (nout,*) WRITE (nout,*) ' Count' WRITE (nout,*) & ' 1 2 3 4 5 >5' WRITE (nout,99998) ncount(1:maxr) WRITE (nout,*) WRITE (nout,*) ' Expect' WRITE (nout,*) & ' 1 2 3 4 5 >5' WRITE (nout,99997) ex(1:maxr) WRITE (nout,*) FLUSH (nout) ifail = 0 CALL x04caf('General',' ',maxr,maxr,cov,ldcov,'Covariance matrix', & ifail) WRITE (nout,*) WRITE (nout,99996) 'Chisq = ', chi WRITE (nout,99995) 'DF = ', df WRITE (nout,99996) 'Prob = ', prob 20 CONTINUE 99999 FORMAT (1X,A,I10) 99998 FORMAT (3X,6I9) 99997 FORMAT (3X,6F9.1) 99996 FORMAT (1X,A,F10.4) 99995 FORMAT (1X,A,F7.1) END PROGRAM g08eafe