NAG Library Manual, Mark 27.3
Interfaces:  FL   CL   CPP   AD 

NAG FL Interface Introduction
Example description
    Program g04gafe

!     G04GAF Example Program Text

!     Mark 27.3 Release. NAG Copyright 2021.

!     .. Use Statements ..
      Use nag_library, Only: g04gaf, nag_wp
!     .. Implicit None Statement ..
      Implicit None
!     .. Parameters ..
      Integer, Parameter               :: nin = 5, nout = 6
!     .. Local Scalars ..
      Real (Kind=nag_wp)               :: alpha, clevel, df1, df2, fstat, icc, &
                                          lci, pvalue, smiss, uci
      Integer                          :: i, ifail, k, mscore, mtype, nrater,  &
                                          nrep, nsubj, rtype
!     .. Local Arrays ..
      Real (Kind=nag_wp), Allocatable  :: score(:,:,:)
!     .. Executable Statements ..

      Write (nout,*) 'G04GAF Example Program Results'
      Write (nout,*)

!     Skip heading in data file
      Read (nin,*)

!     Read in the problem type and size
      Read (nin,*) mtype, rtype, nrep, nsubj, nrater

!     Read in the values used to identify missing scores
      Read (nin,*) mscore, smiss

!     Allocate memory
      Allocate (score(nrep,nsubj,nrater))

!     Read in the rating data
      Do k = 1, nrep
        Do i = 1, nsubj
          Read (nin,*) score(k,i,1:nrater)
        End Do
      End Do

!     Read in alpha for the confidence interval
      Read (nin,*) alpha

!     Calculate the intraclass correlation
      ifail = -1
      Call g04gaf(mtype,rtype,nrep,nsubj,nrater,score,mscore,smiss,alpha,icc,  &
        lci,uci,fstat,df1,df2,pvalue,ifail)
      If (ifail/=0 .And. ifail/=62 .And. ifail/=101 .And. ifail/=102) Then
!       62, 101 and 102 are warnings, all output is still returned
        Stop
      End If

!     Display the results
      Write (nout,99999) 'Intraclass Correlation           :', icc
      clevel = 100.0_nag_wp*(1.0_nag_wp-alpha)
      Write (nout,99998) 'Lower Limit for', clevel, '% CI         :', lci
      Write (nout,99998) 'Upper Limit for', clevel, '% CI         :', uci
      Write (nout,99997) 'F statistic                      :', fstat
      Write (nout,99996) 'Degrees of Freedom 1             :', df1
      Write (nout,99996) 'Degrees of Freedom 2             :', df2
      Write (nout,99995) 'p-value                          :', pvalue

99999 Format (A,1X,F5.2)
99998 Format (A,1X,F4.1,A,1X,F5.2)
99997 Format (A,1X,F5.2)
99996 Format (A,1X,F5.1)
99995 Format (A,1X,F5.3)
    End Program g04gafe