Program g01aefe
! G01AEF Example Program Text
! Mark 29.3 Release. NAG Copyright 2023.
! .. Use Statements ..
Use nag_library, Only: g01aef, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: xmax, xmin
Integer :: iclass, ifail, j, k, n
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: cb(:), x(:)
Integer, Allocatable :: ifreq(:)
! .. Executable Statements ..
Write (nout,*) 'G01AEF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, iclass, k
Allocate (x(n),cb(k),ifreq(k))
! Read in data
Read (nin,*) x(1:n)
Write (nout,99997) 'Number of cases', n
Write (nout,99997) 'Number of classes', k
! Get the class boundaries
If (iclass/=1) Then
Write (nout,*) 'Routine-supplied class boundaries'
Else
Read (nin,*) cb(1:(k-1))
Write (nout,*) 'User-supplied class boundaries'
End If
Write (nout,*)
! Construct the frequency table
ifail = 0
Call g01aef(n,k,x,iclass,cb,ifreq,xmin,xmax,ifail)
! Display results
Write (nout,*) '*** Frequency distribution ***'
Write (nout,*)
Write (nout,*) ' Class Frequency'
Write (nout,*)
Write (nout,99999) ' Up to ', cb(1), ifreq(1)
k = k - 1
If (k>1) Then
Write (nout,99998)(cb(j-1),' to ',cb(j),ifreq(j),j=2,k)
End If
Write (nout,99996) cb(k), ' and over ', ifreq(k+1)
Write (nout,*)
Write (nout,99995) 'Total frequency = ', n
Write (nout,99994) 'Minimum = ', xmin
Write (nout,99994) 'Maximum = ', xmax
99999 Format (1X,A,F8.2,I11)
99998 Format (1X,F8.2,A,F8.2,I11)
99997 Format (1X,A,I4)
99996 Format (1X,F8.2,A,I9)
99995 Format (1X,A,I6)
99994 Format (1X,A,F9.2)
End Program g01aefe