Program g03ehfe
! G03EHF Example Program Text
! Mark 25 Release. NAG Copyright 2014.
! .. Use Statements ..
Use nag_library, Only: g03eaf, g03ecf, g03ehf, nag_wp
! .. Implicit None Statement ..
Implicit None
! .. Parameters ..
Integer, Parameter :: llen = 50, nin = 5, nout = 6
! .. Local Scalars ..
Real (Kind=nag_wp) :: dmin, dstep
Integer :: ellen, i, ifail, ld, ldx, lenc, &
liwk, m, method, n, n1, nsym, olenc
Character (1) :: dist, orient, scal, update
! .. Local Arrays ..
Real (Kind=nag_wp), Allocatable :: cd(:), d(:), dord(:), s(:), x(:,:)
Integer, Allocatable :: ilc(:), iord(:), isx(:), iuc(:), &
iwk(:)
Character (llen), Allocatable :: c(:)
! .. Executable Statements ..
Write (nout,*) 'G03EHF Example Program Results'
Write (nout,*)
! Skip heading in data file
Read (nin,*)
! Read in the problem size
Read (nin,*) n, m
! Read in information on the type of distance matrix to use
Read (nin,*) update, dist, scal
ldx = n
ld = n*(n-1)/2
n1 = n - 1
liwk = 2*n
Allocate (x(ldx,m),isx(m),s(m),d(ld),ilc(n1),iuc(n1),cd(n1),iord(n), &
dord(n),iwk(liwk),c(1))
! Read in the data used to construct distance matrix
Read (nin,*)(x(i,1:m),i=1,n)
! Read in variable inclusion flags
Read (nin,*) isx(1:m)
! Read in scaling
If (scal=='G' .Or. scal=='g') Then
Read (nin,*) s(1:m)
End If
! Compute the distance matrix
ifail = 0
Call g03eaf(update,dist,scal,n,m,x,ldx,isx,s,d,ifail)
! Read in information on the clustering method to use
Read (nin,*) method
! Perform clustering
ifail = 0
Call g03ecf(method,n,d,ilc,iuc,cd,iord,dord,iwk,ifail)
! Produce some example dendrogram
olenc = 0
d_lp: Do
Read (nin,*,Iostat=ifail) orient, dmin, dstep, nsym
If (ifail/=0) Then
Go To 100
End If
! Display the dendogram
Select Case (orient)
Case ('N')
Write (nout,*) 'Dendrogram, Orientation North'
lenc = nsym
ellen = n
Case ('E')
Write (nout,*) 'Dendrogram, Orientation East'
lenc = n
ellen = nsym
Case ('S')
Write (nout,*) 'Dendrogram, Orientation South'
lenc = nsym
ellen = n
Case ('W')
Write (nout,*) 'Dendrogram, Orientation West'
lenc = n
ellen = nsym
End Select
! Check that each element in the character array is sufficiently large
If (llen<ellen) Then
Write (nout,*) &
'Each element of character array C needs to be at least ', ellen
Write (nout,*) 'elements long, current length is ', llen
Go To 100
End If
If (olenc<lenc) Then
! Reallocate matrix
Deallocate (c)
Allocate (c(lenc))
End If
! Generate character array holding the dendogram
ifail = 0
Call g03ehf(orient,n,dord,dmin,dstep,nsym,c,lenc,ifail)
Write (nout,99999) c(1:lenc)
Write (nout,*)
End Do d_lp
100 Continue
99999 Format (1X,A)
End Program g03ehfe