Program g02chfe
! G02CHF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: g02chf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, k, k1, ldcoef, ldcz, ldrz, &
ldrznv, ldsspz, ldwkz, n
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: coef(:,:), cz(:,:), rz(:,:), &
rznv(:,:), sspz(:,:), wkz(:,:)
Real (Kind=nag_wp) :: reslt(13)
! .. Executable Statements ..
Write (nout,*) 'G02CHF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, k
k1 = k + 1
ldcoef = k
ldcz = k
ldrz = k1
ldrznv = k
ldsspz = k1
ldwkz = k
Allocate (coef(ldcoef,3),cz(ldcz,k),rz(ldrz,k1),rznv(ldrznv,k), &
sspz(ldsspz,k1),wkz(ldwkz,k))
! Read in data
Read (nin,*)(sspz(i,1:k1),i=1,k1)
Read (nin,*)(rz(i,1:k1),i=1,k1)
! Display data
Write (nout,*) 'Sums of squares and cross-products about zero:'
Write (nout,99999)(i,i=1,k1)
Write (nout,99998)(i,sspz(i,1:k1),i=1,k1)
Write (nout,*)
Write (nout,*) 'Correlation-like coefficients:'
Write (nout,99999)(i,i=1,k1)
Write (nout,99998)(i,rz(i,1:k1),i=1,k1)
Write (nout,*)
! Fit multiple linear regression model
ifail = 0
Call g02chf(n,k1,k,sspz,ldsspz,rz,ldrz,reslt,coef,ldcoef,rznv,ldrznv,cz, &
ldcz,wkz,ldwkz,ifail)
! Display results
Write (nout,*) 'Vble Coef Std err t-value'
Write (nout,99997)(i,coef(i,1:3),i=1,k)
Write (nout,*)
Write (nout,*) 'Analysis of regression table :-'
Write (nout,*)
Write (nout,*) &
' Source Sum of squares D.F. Mean square F-value'
Write (nout,*)
Write (nout,99996) 'Due to regression', reslt(1:4)
Write (nout,99996) 'About regression', reslt(5:7)
Write (nout,99996) 'Total ', reslt(8:9)
Write (nout,*)
Write (nout,99995) 'Standard error of estimate =', reslt(10)
Write (nout,99995) 'Multiple correlation (R) =', reslt(11)
Write (nout,99995) 'Determination (R squared) =', reslt(12)
Write (nout,99995) 'Corrected R squared =', reslt(13)
Write (nout,*)
Write (nout,*) 'Inverse of correlation matrix of independent variables:'
Write (nout,99994)(i,i=1,k)
Write (nout,99993)(i,rznv(i,1:k),i=1,k)
Write (nout,*)
Write (nout,*) 'Modified inverse matrix:'
Write (nout,99994)(i,i=1,k)
Write (nout,99993)(i,cz(i,1:k),i=1,k)
99999 Format (1X,3I10)
99998 Format (1X,I4,3F10.4)
99997 Format (1X,I3,3F12.4)
99996 Format (1X,A,F14.4,F8.0,2F14.4)
99995 Format (1X,A,F8.4)
99994 Format (1X,2I10)
99993 Format (1X,I4,2F10.4)
End Program g02chfe