Program g03cafe
! G03CAF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: g03caf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, l, ldfl, ldx, liwk, lres, &
lwk, lwt, m, n, nfac, nvar
Character (1) :: matrix, weight
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: com(:), e(:), fl(:,:), psi(:), &
res(:), wk(:), wt(:), x(:,:)
Real (Kind=nag_wp) :: stat(4)
Integer :: iop(5)
Integer, Allocatable :: isx(:), iwk(:)
! .. Intrinsic Procedures ..
Intrinsic :: max
! .. Executable Statements ..
Write (nout,*) 'G03CAF Example Program Results'
Write (nout,*)
! Skip headings in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) matrix, weight, n, m, nvar, nfac
lwk = (5*nvar*nvar+33*nvar-4)/2
If (matrix=='C' .Or. matrix=='c') Then
lwt = 0
ldx = m
Else
If (weight=='W' .Or. weight=='w') Then
lwt = n
Else
lwt = 0
End If
ldx = n
lwk = max(lwk,n*nvar+7*nvar+nvar*(nvar-1)/2)
End If
ldfl = nvar
lres = nvar*(nvar-1)/2
liwk = 4*nvar + 2
Allocate (x(ldx,m),isx(m),wt(lwt),e(nvar),com(nvar),psi(nvar),res(lres), &
fl(ldfl,nfac),iwk(liwk),wk(lwk))
! Read in the data
If (lwt>0) Then
Read (nin,*)(x(i,1:m),wt(i),i=1,ldx)
Else
Read (nin,*)(x(i,1:m),i=1,ldx)
End If
! Read in variable inclusion flags
Read (nin,*) isx(1:m)
! Read in options
Read (nin,*) iop(1:5)
! Fit factor analysis model
ifail = -1
Call g03caf(matrix,weight,n,m,x,ldx,nvar,isx,nfac,wt,e,stat,com,psi,res, &
fl,ldfl,iop,iwk,wk,lwk,ifail)
If (ifail/=0) Then
If (ifail<=4) Then
Go To 100
End If
End If
! Display results
Write (nout,*) ' Eigenvalues'
Write (nout,*)
Write (nout,99998) e(1:nvar)
Write (nout,*)
Write (nout,99997) ' Test Statistic = ', stat(2)
Write (nout,99997) ' df = ', stat(3)
Write (nout,99997) ' Significance level = ', stat(4)
Write (nout,*)
Write (nout,*) ' Residuals'
Write (nout,*)
l = 1
Do i = 1, nvar - 1
Write (nout,99999) res(l:(l+i-1))
l = l + i
End Do
Write (nout,*)
Write (nout,*) ' Loadings, Communalities and PSI'
Write (nout,*)
Do i = 1, nvar
Write (nout,99999) fl(i,1:nfac), com(i), psi(i)
End Do
100 Continue
99999 Format (2X,9F8.3)
99998 Format (2X,6E12.4)
99997 Format (A,F6.3)
End Program g03cafe