Program g03dafe
! G03DAF Example Program Text
! Mark 28.3 Release. NAG Copyright 2022.
! .. Use Statements ..
Use nag_library, Only: g03daf, nag_wp, x04caf
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: df, sig, stat
Integer :: i, ifail, ldgmn, ldx, lgc, lwk, lwt, &
m, n, ng, nvar
Character (1) :: weight
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: det(:), gc(:), gmn(:,:), wk(:), &
wt(:), x(:,:)
Integer, Allocatable :: ing(:), isx(:), iwk(:), nig(:)
! .. Intrinsic Procedures ..
Intrinsic :: count
! .. Executable Statements ..
Write (nout,*) 'G03DAF Example Program Results'
Write (nout,*)
Flush (nout)
! Skip headings in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, m, ng, weight
If (weight=='W' .Or. weight=='w') Then
lwt = n
Else
lwt = 0
End If
ldx = n
Allocate (x(ldx,m),ing(n),wt(lwt),isx(m))
! Read in data
If (lwt>0) Then
Read (nin,*)(x(i,1:m),ing(i),wt(i),i=1,n)
Else
Read (nin,*)(x(i,1:m),ing(i),i=1,n)
End If
! Read in variable inclusion flags
Read (nin,*) isx(1:m)
! Calculate NVAR
nvar = count(isx(1:m)==1)
ldgmn = ng
lgc = (ng+1)*nvar*(nvar+1)/2
lwk = n*(nvar+1)
Allocate (nig(ng),gmn(ldgmn,nvar),det(ng),gc(lgc),wk(lwk),iwk(ng))
! Compute test statistic
ifail = 0
Call g03daf(weight,n,m,x,ldx,isx,nvar,ing,ng,wt,nig,gmn,ldgmn,det,gc, &
stat,df,sig,wk,iwk,ifail)
! Display results
ifail = 0
Call x04caf('General',' ',ng,nvar,gmn,ldgmn,'Group means',ifail)
Write (nout,*)
Write (nout,*) ' LOG of determinants'
Write (nout,*)
Write (nout,99999) det(1:ng)
Write (nout,*)
Write (nout,99998) ' STAT = ', stat
Write (nout,99998) ' DF = ', df
Write (nout,99998) ' SIG = ', sig
99999 Format (1X,3F10.4)
99998 Format (1X,A,F7.4)
End Program g03dafe