Program g04dafe ! G04DAF Example Program Text ! Mark 24 Release. NAG Copyright 2012. ! .. Use Statements .. Use nag_library, Only: g04bbf, g04daf, nag_wp ! .. Implicit None Statement .. Implicit None ! .. Parameters .. Integer, Parameter :: nin = 5, nout = 6 ! .. Local Scalars .. Real (Kind=nag_wp) :: gmean, rdf, rms, tol Integer :: i, iblock, ifail, irdf, ldc, ldct, & ldtabl, lit, n, nc, nt Logical :: usetx ! .. Local Arrays .. Real (Kind=nag_wp), Allocatable :: bmean(:), c(:,:), ct(:,:), ef(:), & est(:), r(:), tabl(:,:), tmean(:), & tx(:), wk(:), y(:) Integer, Allocatable :: irep(:), it(:) Character (11), Allocatable :: names(:) ! .. Intrinsic Procedures .. Intrinsic :: abs ! .. Executable Statements .. Write (nout,*) 'G04DAF Example Program Results' Write (nout,*) ! Skip heading in data file Read (nin,*) ! Read in problem size for G04BBF 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 for G04BBF Read (nin,*) y(1:n) If (nt>1) Then Read (nin,*) it(1:n) End If ! Don't use TX when calling G04DAF usetx = .False. ! Read in the number of contrasts Read (nin,*) nc ! Using first 4 rows of TABL in G04BBF next NC rows in G04DAF ldtabl = nc + 4 ldct = nt Allocate (ct(ldct,nc),est(nc),tabl(ldtabl,5),tx(nt),names(nc)) ! Read in the constrasts and their names Do i = 1, nc Read (nin,*) ct(1:nt,i) Read (nin,99999) names(i) End Do ! 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 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 ', tabl(1,1:5) End If 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,*) ! Extract the residual mean square and degrees of freedom from ANOVA ! table rms = tabl(3,3) rdf = tabl(3,1) ! Compute sums of squares for contrast ifail = -1 Call g04daf(nt,tmean,irep,rms,rdf,nc,ct,ldct,est,tabl(5,1),ldtabl,tol, & usetx,tx,ifail) If (ifail/=0) Then If (ifail/=2) Then Go To 100 End If End If ! Display results from G04DAF Write (nout,*) ' Orthogonal Contrasts' Write (nout,*) Write (nout,99998)(names(i),tabl(i+4,1:5),i=1,nc) 100 Continue 99999 Format (A) 99998 Format (A,3X,F3.0,2X,F10.1,2X,F10.1,2X,F10.3,2X,F9.4) End Program g04dafe