PROGRAM g03ccfe ! G03CCF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g03caf, g03ccf, nag_wp, x04caf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. INTEGER :: i, ifail, ldfl, ldfs, ldr, ldx, & liwk, lres, lwk, lwt, m, n, nfac, & nvar, tdr CHARACTER (80) :: fmt CHARACTER (1) :: matrix, method, rotate, weight ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: com(:), e(:), fl(:,:), fs(:,:), & psi(:), r(:,:), res(:), wk(:), & wt(:), x(:,:) REAL (KIND=nag_wp) :: stat(4) INTEGER :: iop(5) INTEGER, ALLOCATABLE :: isx(:), iwk(:) ! .. Intrinsic Functions .. INTRINSIC count, max ! .. Executable Statements .. WRITE (nout,*) 'G03CCF Example Program Results' WRITE (nout,*) FLUSH (nout) ! Skip headings in data file READ (nin,*) ! Read in the problem size READ (nin,*) matrix, weight, n, m, nfac 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 END IF ALLOCATE (x(ldx,m),isx(m),wt(lwt)) ! 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) ! Calculate NVAR nvar = count(isx(1:m)==1) ! Do not apply a rotation rotate = 'U' tdr = 1 ldr = 1 lres = nvar*(nvar-1)/2 liwk = 4*nvar + 2 lwk = 5*nvar*nvar + 33*nvar - 4/2 IF (matrix/='C' .AND. matrix/='c') THEN lwk = max(lwk,n*nvar+7*nvar+nvar*(nvar-1)/2) END IF lwk = max(lwk,nvar) ldfs = nvar ldfl = nvar ALLOCATE (e(nvar),com(nvar),psi(nvar),res(lres),fl(ldfl,nfac),wk(lwk), & iwk(liwk),fs(ldfs,nfac),r(ldr,tdr)) ! 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 20 END IF END IF ! Display results WRITE (nout,*) ' Loadings, Communalities and PSI' WRITE (nout,*) WRITE (fmt,99999) '(', nfac + 2, '(1X,F8.3))' WRITE (nout,fmt) (fl(i,1:nfac),com(i),psi(i),i=1,nvar) ! Read in details of how to compute factor scores READ (nin,*) method ! Compute factor scores ifail = 0 CALL g03ccf(method,rotate,nvar,nfac,fl,ldfl,psi,e,r,ldr,fs,ldfs,wk, & ifail) ! Display factor score coefficients WRITE (nout,*) FLUSH (nout) ifail = 0 CALL x04caf('General',' ',nvar,nfac,fs,ldfs,'Factor score coefficients' & ,ifail) 20 CONTINUE 99999 FORMAT (A,I0,A) END PROGRAM g03ccfe