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

NAG FL Interface Introduction
Example description
    Program g02byfe

!     G02BYF Example Program Text

!     Mark 29.3 Release. NAG Copyright 2023.

!     .. 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