PROGRAM g02byfe ! G02BYF Example Program Text ! Mark 23 Release. NAG Copyright 2011. ! .. Use Statements .. USE nag_library, ONLY : g02bxf, g02byf, nag_wp, x04caf ! .. Implicit None Statement .. IMPLICIT NONE ! .. Parameters .. INTEGER, PARAMETER :: nin = 5, nout = 6 ! .. Local Scalars .. INTEGER :: i, ifail, ldp, ldr, ldx, lwt, m, n, & nx, ny CHARACTER (1) :: weight ! .. Local Arrays .. REAL (KIND=nag_wp), ALLOCATABLE :: p(:,:), r(:,:), std(:), v(:,:), & wk(:), wt(:), x(:,:), xbar(:) INTEGER, ALLOCATABLE :: isz(:) ! .. Executable Statements .. WRITE (nout,*) 'G02BYF Example Program Results' WRITE (nout,*) FLUSH (nout) ! Skip heading in data file READ (nin,*) ! Read in the problem size READ (nin,*) weight, n, m IF (weight=='W' .OR. weight=='w') THEN lwt = n ELSE lwt = 0 END IF ldp = m ldr = m ldx = n ALLOCATE (p(ldp,m),v(ldr,m),std(m),wk(m*m),wt(lwt),x(ldx,m),xbar(m), & isz(m),r(ldr,m)) ! Read in data READ (nin,*) (x(i,1:m),i=1,n) ! Read in number of variables and variable flags for partial correlation ! coefficients. READ (nin,*) ny, nx READ (nin,*) isz(1:m) ! Calculate correlation matrix ifail = 0 CALL g02bxf(weight,n,m,x,ldx,wt,xbar,std,v,ldr,r,ifail) ! Calculate partial correlation matrix ifail = 0 CALL g02byf(m,ny,nx,isz,r,ldr,p,ldp,wk,ifail) ! Display results ifail = 0 CALL x04caf('Upper','Non-unit',m,m,r,ldr,'Correlation matrix',ifail) WRITE (nout,*) FLUSH (nout) ifail = 0 CALL x04caf('Upper','Unit',ny,ny,p,ldp,'Partial Correlation matrix', & ifail) END PROGRAM g02byfe