PROGRAM g08affe ! G08AFF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g08aff, nag_wp ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. REAL (KIND=nag_wp) :: h, p INTEGER :: i, ifail, k, lx, nhi, nlo ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: w(:), x(:) INTEGER, ALLOCATABLE :: l(:) ! .. Intrinsic Functions .. INTRINSIC sum ! .. Executable Statements .. WRITE (nout,*) 'G08AFF Example Program Results' WRITE (nout,*) ! Skip heading in data file READ (nin,*) ! Read in problem size READ (nin,*) k ALLOCATE (l(k)) ! Read in number of observations in each sample READ (nin,*) l(1:k) ! Calculate total number of observations lx = sum(l(1:k)) ALLOCATE (x(lx),w(lx)) ! Read in data READ (nin,*) x(1:lx) ! Display title WRITE (nout,*) 'Kruskal-Wallis test' WRITE (nout,*) ! Display input data WRITE (nout,*) 'Data values' WRITE (nout,*) WRITE (nout,*) ' Group Observations' nlo = 1 DO i = 1, k nhi = nlo + l(i) - 1 WRITE (nout,99999) i, x(nlo:nhi) nlo = nlo + l(i) END DO ! Perform ANOVA ifail = 0 CALL g08aff(x,lx,l,k,w,h,p,ifail) ! Display results WRITE (nout,*) WRITE (nout,99998) 'Test statistic ', h WRITE (nout,99997) 'Degrees of freedom ', k - 1 WRITE (nout,99998) 'Significance ', p 99999 FORMAT (1X,I5,5X,10F4.0) 99998 FORMAT (1X,A,F9.3) 99997 FORMAT (1X,A,I9) END PROGRAM g08affe