Program g01abfe
! G01ABF Example Program Text
! Mark 26.1 Release. NAG Copyright 2016.
! .. Use Statements ..
Use nag_library, Only: g01abf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Integer :: i, ifail, iwt, n
! .. Local Arrays ..
Real (Kind=nag_wp) :: res(13)
Real (Kind=nag_wp), Allocatable :: wt(:), wtin(:), x1(:), x2(:)
! .. Executable Statements ..
Write (nout,*) 'G01ABF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, iwt
Allocate (wt(n),wtin(n),x1(n),x2(n))
! Read in data
Read (nin,*)(x1(i),x2(i),i=1,n)
If (iwt==1) Then
Read (nin,*) wtin(1:n)
wt(1:n) = wtin(1:n)
End If
! Display data
Write (nout,99999) 'Number of cases', n
Write (nout,*) 'Data as input -'
Write (nout,*) &
' Var 1 Var 2 Var 1 Var 2 Var 1 Var 2'
Write (nout,99995)(x1(i),x2(i),i=1,n)
If (iwt==1) Then
Write (nout,*) 'Weights as input -'
Write (nout,99994) wtin(1:n)
End If
Write (nout,*)
! Calculate summary statistics
ifail = -1
Call g01abf(n,x1,x2,iwt,wt,res,ifail)
If (ifail/=0) Then
If (ifail/=2) Then
Go To 100
End If
End If
! Display results
Write (nout,99999) 'No. of valid cases', iwt
Write (nout,99993) 'Variable 1', 'Variable 2'
Write (nout,99998) 'Mean ', res(1), res(2)
Write (nout,99997) 'Corr SSP', res(5), res(6), res(7)
Write (nout,99998) 'Minimum ', res(9), res(11)
Write (nout,99998) 'Maximum ', res(10), res(12)
Write (nout,99998) 'Sum of weights ', res(13)
If (ifail==0) Then
Write (nout,99998) 'Std devn', res(3), res(4)
Write (nout,99996) 'Correln ', res(8)
Else
Write (nout,*) 'Std devn and Correln not defined'
End If
100 Continue
99999 Format (1X,A,I5)
99998 Format (1X,A,F15.1,F30.1)
99997 Format (1X,A,3E15.5)
99996 Format (1X,A,F30.4)
99995 Format (5X,6F11.1)
99994 Format (13X,F9.3)
99993 Format (13X,A,20X,A)
End Program g01abfe