Program g02bsfe
! G02BSF Example Program Text
! Mark 28.6 Release. NAG Copyright 2022.
! .. Use Statements ..
Use nag_library, Only: g02bsf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, itype, ldcnt, ldrr, ldx, &
m, n, ncases
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: cnt(:,:), rr(:,:), work1(:), &
work2(:), x(:,:), xmiss(:)
Integer, Allocatable :: kworka(:), kworkb(:), kworkc(:), &
kworkd(:), miss(:)
! .. Executable Statements ..
Write (nout,*) 'G02BSF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, m, itype
ldcnt = m
ldrr = m
ldx = n
Allocate (cnt(ldcnt,m),rr(ldrr,m),work1(n),work2(n),x(ldx,m),xmiss(m), &
kworka(n),kworkb(n),kworkc(n),kworkd(n),miss(m))
! Read in data
Read (nin,*)(x(i,1:m),i=1,n)
! Read in missing value flags
Read (nin,*) miss(1:m)
Read (nin,*) xmiss(1:m)
! Display data
Write (nout,99999) 'Number of variables (columns) =', m
Write (nout,99999) 'Number of cases (rows) =', n
Write (nout,*)
Write (nout,*) 'Data matrix is:-'
Write (nout,*)
Write (nout,99998)(i,i=1,m)
Write (nout,99997)(i,x(i,1:m),i=1,n)
Write (nout,*)
! Calculate correlation coefficients
ifail = 0
Call g02bsf(n,m,x,ldx,miss,xmiss,itype,rr,ldrr,ncases,cnt,ldcnt,kworka, &
kworkb,kworkc,kworkd,work1,work2,ifail)
! Display results
Write (nout,*) 'Matrix of rank correlation coefficients:'
Write (nout,*) 'Upper triangle -- Spearman''s'
Write (nout,*) 'Lower triangle -- Kendall''s tau'
Write (nout,*)
Write (nout,99998)(i,i=1,m)
Write (nout,99997)(i,rr(i,1:m),i=1,m)
Write (nout,*)
Write (nout,99999) &
'Minimum number of cases used for any pair of variables:', ncases
Write (nout,*)
Write (nout,*) 'Numbers used for each pair are:'
Write (nout,99998)(i,i=1,m)
Write (nout,99997)(i,cnt(i,1:m),i=1,m)
99999 Format (1X,A,I5)
99998 Format (1X,3I12)
99997 Format (1X,I3,3F12.4)
End Program g02bsfe