Program g04bbfe
! G04BBF Example Program Text
! Mark 30.1 Release. NAG Copyright 2024.
! .. Use Statements ..
Use nag_library, Only: g04bbf, nag_wp, x04caf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: ldtabl = 4, nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: gmean, tol
Integer :: iblock, ifail, irdf, ldc, lit, n, nt
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: bmean(:), c(:,:), ef(:), r(:), &
tmean(:), wk(:), y(:)
Real (Kind=nag_wp) :: tabl(ldtabl,5)
Integer, Allocatable :: irep(:), it(:)
! .. Intrinsic Procedures ..
Intrinsic :: abs
! .. Executable Statements ..
Write (nout,*) 'G04BBF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, nt, iblock
ldc = nt
If (nt>1) Then
lit = n
Else
lit = 1
End If
Allocate (y(n),bmean(abs(iblock)),tmean(nt),irep(nt),c(ldc,nt),r(n), &
ef(nt),wk(3*nt),it(lit))
! Read in the data and plot information
Read (nin,*) y(1:n)
If (nt>1) Then
Read (nin,*) it(1:n)
End If
! Use default tolerance
tol = 0.0E0_nag_wp
! Use standard degrees of freedom
irdf = 0
! Calculate the ANOVA table
ifail = 0
Call g04bbf(n,y,iblock,nt,it,gmean,bmean,tmean,tabl,ldtabl,c,ldc,irep,r, &
ef,tol,irdf,wk,ifail)
! Display results
Write (nout,*) ' ANOVA table'
Write (nout,*)
Write (nout,*) ' Source df SS MS F', &
' Prob'
Write (nout,*)
Write (nout,99998) ' Blocks ', tabl(1,1:5)
Write (nout,99998) ' Treatments ', tabl(2,1:5)
Write (nout,99998) ' Residual ', tabl(3,1:3)
Write (nout,99998) ' Total ', tabl(4,1:2)
Write (nout,*)
Write (nout,*) ' Efficiency Factors'
Write (nout,*)
Write (nout,99999) ef(1:nt)
Write (nout,*)
Write (nout,99997) ' Grand Mean', gmean
Write (nout,*)
Write (nout,*) ' Treatment Means'
Write (nout,*)
Write (nout,99999) tmean(1:nt)
Write (nout,*)
Flush (nout)
ifail = 0
Call x04caf('Lower','B',nt,nt,c,ldc, &
'Standard errors of differences between means',ifail)
99999 Format (8F10.2)
99998 Format (A,3X,F3.0,2X,3(F10.2,2X),F9.4)
99997 Format (A,F10.2)
End Program g04bbfe