Program g04dbfe
! G04DBF Example Program Text
! Mark 26.2 Release. NAG Copyright 2017.
! .. Use Statements ..
Use nag_library, Only: g04bbf, g04dbf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: clevel, gmean, rdf, tol
Integer :: i, iblock, ifail, ij, irdf, j, ldc, &
lit, n, nt
Character (1) :: typ
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: bmean(:), c(:,:), cil(:), ciu(:), &
ef(:), r(:), tmean(:), wk(:), y(:)
Real (Kind=nag_wp) :: table(4,5)
Integer, Allocatable :: irep(:), isig(:), it(:)
Character (1) :: star(2)
! .. Intrinsic Procedures ..
Intrinsic :: abs
! .. Executable Statements ..
Write (nout,*) 'G04DBF 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),cil(nt*(nt-1)/2),ciu(nt*(nt-1)/2),isig(nt*(nt- &
1)/2))
! Read in the data and plot information
Read (nin,*) y(1:n)
If (nt>1) Then
Read (nin,*) it(1:n)
End If
! Read in the type of level for the CIs
Read (nin,*) typ, clevel
! 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,table,4,c,ldc,irep,r,ef, &
tol,irdf,wk,ifail)
! Display results from G04BBF
Write (nout,*) ' ANOVA table'
Write (nout,*)
Write (nout,*) ' Source df SS MS F', &
' Prob'
Write (nout,*)
If (iblock>1) Then
Write (nout,99998) ' Blocks ', table(1,1:5)
End If
Write (nout,99998) ' Treatments', table(2,1:5)
Write (nout,99998) ' Residual ', table(3,1:3)
Write (nout,99998) ' Total ', table(4,1:2)
Write (nout,*)
Write (nout,*) ' Treatment means'
Write (nout,*)
Write (nout,99999) tmean(1:nt)
Write (nout,*)
! Extract the residual degrees of freedom
rdf = table(3,1)
! Calculate simultaneous CIs
ifail = 0
Call g04dbf(typ,nt,tmean,rdf,c,ldc,clevel,cil,ciu,isig,ifail)
! Display results from G04DBF
Write (nout,*) ' Simultaneous Confidence Intervals'
Write (nout,*)
star(2) = '*'
star(1) = ' '
ij = 0
Do i = 1, nt
Do j = 1, i - 1
ij = ij + 1
Write (nout,99997) i, j, cil(ij), ciu(ij), star(isig(ij)+1)
End Do
End Do
99999 Format (10F8.3)
99998 Format (A,3X,F3.0,2X,2(F10.1,2X),F10.3,2X,F9.4)
99997 Format (2X,2I2,3X,2(F10.3,3X),A)
End Program g04dbfe