Keyword: クラスター指示変数, 計算, 多変量解析
概要
本サンプルはクラスター指示変数の計算を行うFortranによるサンプルプログラムです。 本サンプルは以下に示されるデータについてクラスター指示変数の計算を行います。
※本サンプルはnAG Fortranライブラリに含まれるルーチン g03ejf() のExampleコードです。本サンプル及びルーチンの詳細情報は g03ejf のマニュアルページをご参照ください。
ご相談やお問い合わせはこちらまで
入力データ
(本ルーチンの詳細はg03ejf のマニュアルページを参照)| このデータをダウンロード |
G03EJF Example Program Data 5 3 : N,M (G03EAF) 'I' 'S' 'U' : UPDATE,DIST,SCAL (G03EAF) 1 5.0 2.0 2 1.0 1.0 3 4.0 3.0 4 1.0 2.0 5 5.0 0.0 : End of X (G03EAF) 0 1 1 : ISX 5 : METHOD (G03ECF) 'A' 'B' 'C' 'D' 'E' : Row names (NAME) 2 0.0 : K, DLEVEL
- 1行目はタイトル行で読み飛ばされます。
- 2行目に観測値の数(n=5)と変数の数(m=3)を指定しています。
- 4行目には既存の行列が更新されるか(update='I':距離が行列Dに追加される前に行列Dは初期化される)、計算される距離の種類(dist='S':ユークリッド平方距離)、使用される変数の標準化(scal='U':スケーリングしない)を指定しています。
- 4〜8行目に変数の値(x)を指定しています。
- 9行目に変数がクラスター指示変数の計算に含まれるどうかを示すフラグ(isx)を指定しています。"1"の場合は計算に含まれます。
- 10行目にクラスタリングの手法(method=5:メディアン法)を指定しています。
- 11行目は行の名前(row_name)を指定しています。
- 12行目に特定の数のクラスタ−が必要かどうかその数(k=2)と必要なクラスターが見つかる際の距離(dlevel=0.0)を指定しています。
出力結果
(本ルーチンの詳細はg03ejf のマニュアルページを参照)| この出力例をダウンロード |
G03EJF Example Program Results
Distance Clusters Joined
1.000 B D
2.000 A C
6.500 A E
14.125 A B
Allocation to 2 clusters
Clusters found at distance 6.500
Object Cluster
A 1
B 2
C 1
D 2
E 1
- 3〜8行目に距離と結合されたクラスターが出力されています。
- 10行目に2つのクラスターに割り当てられたことが出力されています。
- 11行目にクラスターが見つかった際の距離が出力されています。
- 13〜19行目にオブジェクトがどのクラスターに属するかが出力されています。
ソースコード
(本ルーチンの詳細はg03ejf のマニュアルページを参照)
※本サンプルソースコードは科学技術・統計計算ライブラリである「nAG Fortranライブラリ」のルーチンを呼び出します。
サンプルのコンパイル及び実行方法
| このソースコードをダウンロード |
PROGRAM g03ejfe
! G03EJF Example Program Text
! Mark 23 Release. nAG Copyright 2011.
! .. Use Statements ..
USE nag_library, ONLY : g03eaf, g03ecf, g03ejf, nag_wp
! .. Implicit None Statement ..
IMPLICIT NONE
! .. Parameters ..
INTEGER, PARAMETER :: nin = 5, nout = 6, rnlen = 3
! .. Local Scalars ..
REAL (KIND=nag_wp) :: dlevel
INTEGER :: i, ifail, k, ld, ldx, liwk, m, &
method, n, n1
CHARACTER (1) :: dist, scal, update
! .. Local Arrays ..
REAL (KIND=nag_wp), ALLOCATABLE :: cd(:), d(:), dord(:), s(:), x(:,:)
INTEGER, ALLOCATABLE :: ic(:), ilc(:), iord(:), isx(:), &
iuc(:), iwk(:)
CHARACTER (rnlen), ALLOCATABLE :: row_name(:)
! .. Executable Statements ..
WRITE (nout,*) 'G03EJF 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),ic(n),row_name(n))
! 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
! Read in first RNLEN characters of row names. Used to make example
! output easier to read
READ (nin,*) row_name(1:n)
! Perform clustering
ifail = 0
CALL g03ecf(method,n,d,ilc,iuc,cd,iord,dord,iwk,ifail)
! Display full clustering information
WRITE (nout,*) ' Distance Clusters Joined'
WRITE (nout,*)
DO i = 1, n - 1
WRITE (nout,99999) cd(i), row_name(ilc(i)), row_name(iuc(i))
END DO
WRITE (nout,*)
! Read in number of clusters required (K) and
! distance (DLEVEL). If K > 0 then DLEVEL is
! ignored (i.e. attempt to find K clusters,
! irrespective of distance), else all clusters at
! level DLEVEL are used
READ (nin,*) k, dlevel
! Compute cluster indicator
ifail = 0
CALL g03ejf(n,cd,iord,dord,k,dlevel,ic,ifail)
! Display the indicators
WRITE (nout,99998) ' Allocation to ', k, ' clusters'
WRITE (nout,99996) ' Clusters found at distance ', dlevel
WRITE (nout,*)
WRITE (nout,*) ' Object Cluster'
WRITE (nout,*)
WRITE (nout,99997) (row_name(i),ic(i),i=1,n)
99999 FORMAT (1X,F10.3,5X,2A)
99998 FORMAT (1X,A,I0,A)
99997 FORMAT (6X,A,5X,I2)
99996 FORMAT (1X,A,F0.3)
END PROGRAM g03ejfe
