Program g02bnfe
! G02BNF Example Program Text
! Mark 29.2 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: g02bnf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, itype, ldrr, ldx, m, n
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: rr(:,:), work1(:), work2(:), x(:,:)
Integer, Allocatable :: kworka(:), kworkb(:)
! .. Executable Statements ..
Write (nout,*) 'G02BNF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, m, itype
ldrr = m
ldx = n
Allocate (rr(ldrr,m),work1(m),work2(m),x(ldx,m),kworka(n),kworkb(n))
! Read in data
Read (nin,*)(x(i,1:m),i=1,n)
! 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 g02bnf(n,m,x,ldx,itype,rr,ldrr,kworka,kworkb,work1,work2,ifail)
! Display results
Write (nout,*) 'Matrix of ranks:-'
Write (nout,99998)(i,i=1,m)
Write (nout,99997)(i,x(i,1:m),i=1,n)
Write (nout,*)
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)
99999 Format (1X,A,I5)
99998 Format (1X,3I12)
99997 Format (1X,I3,3F12.4)
End Program g02bnfe