PROGRAM g03effe

!      G03EFF Example Program Text

!      Mark 23 Release. NAG Copyright 2011.

!      .. Use Statements ..
       USE nag_library, ONLY : g03eff, nag_wp, x04caf
!      .. Implicit None Statement ..
       IMPLICIT NONE
!      .. Parameters ..
       INTEGER, PARAMETER              :: nin = 5, nout = 6
!      .. Local Scalars ..
       INTEGER                         :: i, ifail, k, ldc, ldx, lwt, m,       &
                                          maxit, n, nvar
       CHARACTER (1)                   :: weight
!      .. Local Arrays ..
       REAL (KIND=nag_wp), ALLOCATABLE :: cmeans(:,:), css(:), csw(:), wk(:),  &
                                          wt(:), x(:,:)
       INTEGER, ALLOCATABLE            :: inc(:), isx(:), iwk(:), nic(:)
!      .. Intrinsic Functions ..
       INTRINSIC                          count
!      .. Executable Statements ..
       WRITE (nout,*) 'G03EFF Example Program Results'
       WRITE (nout,*)

!      Skip heading in the data file
       READ (nin,*)

!      Read in the problem size and control parameters
       READ (nin,*) weight, n, m, k, maxit

       IF (weight=='W' .OR. weight=='w') THEN
          lwt = n
       ELSE
          lwt = 0
       END IF
       ldx = n
       ALLOCATE (x(ldx,m),wt(n),isx(m))

!      Read in data
       IF (lwt>0) THEN
          READ (nin,*) (x(i,1:m),wt(i),i=1,n)
       ELSE
          READ (nin,*) (x(i,1:m),i=1,n)
       END IF

!      Read in variable inclusion flags
       READ (nin,*) isx(1:m)

!      Calculate NVAR
       nvar = count(isx(1:m)==1)

       ldc = k
       ALLOCATE (cmeans(ldc,nvar),inc(n),nic(k),css(k),csw(k),iwk(n+3*k), &
          wk(n+2*k))

!      Read in the initial cluster centres
       READ (nin,*) (cmeans(i,1:nvar),i=1,k)

!      Perform k means clustering
       ifail = 0
       CALL g03eff(weight,n,m,x,ldx,isx,nvar,k,cmeans,ldc,wt,inc,nic,css,csw, &
          maxit,iwk,wk,ifail)

!      Display results
       WRITE (nout,*) ' The cluster each point belongs to'
       WRITE (nout,99999) inc(1:n)
       WRITE (nout,*)
       WRITE (nout,*) ' The number of points in each cluster'
       WRITE (nout,99999) nic(1:k)
       WRITE (nout,*)
       WRITE (nout,*) ' The within-cluster sum of weights of each cluster'
       WRITE (nout,99998) csw(1:k)
       WRITE (nout,*)
       WRITE (nout,*) ' The within-cluster sum of squares of each cluster'
       WRITE (nout,99997) css(1:k)
       WRITE (nout,*)
       FLUSH (nout)
       ifail = 0
       CALL x04caf('General',' ',k,nvar,cmeans,ldc,'The final cluster centres' &
          ,ifail)

99999  FORMAT (1X,10I6)
99998  FORMAT (1X,5F9.2)
99997  FORMAT (1X,5F13.4)
    END PROGRAM g03effe