Keyword: 分散分析, ANOVA, 信頼区間の計算
概要
本サンプルは分散分析(ANOVA: Analysis of Variance)で計算した処理平均の差の信頼区間の計算を行うFortranによるサンプルプログラムです。 本サンプルは以下に示される観測値をg04bbf関数を呼び出して分散分析し、分散分析表、処理平均や処理平均の差の同時信頼区間を出力します。
※本サンプルはnAG Fortranライブラリに含まれるルーチン g04dbf() のExampleコードです。本サンプル及びルーチンの詳細情報は g04dbf のマニュアルページをご参照ください。
ご相談やお問い合わせはこちらまで
入力データ
(本ルーチンの詳細はg04dbf のマニュアルページを参照)| このデータをダウンロード |
G04DBF Example Program Data 26 4 1 :: N, NT, IBLOCK (G04BBF) 3 2 4 3 1 5 7 8 4 10 6 3 2 1 2 4 2 3 1 10 12 8 5 12 10 9 :: End of Y (G04BBF) 1 1 1 1 1 1 2 2 2 2 2 3 3 3 3 3 3 3 3 4 4 4 4 4 4 4 :: End of IT (G04BBF) 'T' .95 :: TYP, CLEVEL
- 1行目はタイトル行で読み飛ばされます。
- 2行目に観測値の数(n=26)と処理数(nt=4)とブロック構造(iblock=1)を指定しています。ブロック構造"1"はブロックがなく完全無作為化法を意味しています。
- 3〜6行目に観測値のデータ(y)を指定しています。
- 7〜10行目に各観測値が何回目の処理で処理されるか処理回数(it)を指定しています。
- 11行目に使用する手法(typ='T':Tukey-Kramer法)と信頼水準(clevel=.95)を指定しています。
出力結果
(本ルーチンの詳細はg04dbf のマニュアルページを参照)| この出力例をダウンロード |
G04DBF Example Program Results ANOVA table Source df SS MS F Prob Treatments 3. 239.9 80.0 24.029 0.0000 Residual 22. 73.2 3.3 Total 25. 313.1 Treatment means 3.000 7.000 2.250 9.429 Simultaneous Confidence Intervals 2 1 0.933 7.067 * 3 1 -3.486 1.986 3 2 -7.638 -1.862 * 4 1 3.610 9.247 * 4 2 -0.538 5.395 4 3 4.557 9.800 *
- 3〜9行目に分散分析表が出力されています。
- 7行目に処理の自由度、平方和、平均平方、F統計量と有意水準が出力されています。
- 8行目に残差の自由度、平方和と平均平方が出力されています。
- 9行目に自由度と平方和の合計が出力されています。
- 13行目には各処理の処理平均が出力されています。
- 17〜22行目には処理平均の差の信頼区間の下限、上限が出力されています。"*"マークは処理平均の差が有意であることを示しています。
ソースコード
(本ルーチンの詳細はg04dbf のマニュアルページを参照)
※本サンプルソースコードは科学技術・統計計算ライブラリである「nAG Fortranライブラリ」のルーチンを呼び出します。
サンプルのコンパイル及び実行方法
| このソースコードをダウンロード |
PROGRAM g04dbfe
! G04DBF Example Program Text
! Mark 23 Release. nAG Copyright 2011.
! .. Use Statements ..
USE nag_library, ONLY : g04bbf, g04dbf, nag_wp
! .. Implicit None Statement ..
IMPLICIT NONE
! .. Parameters ..
INTEGER, PARAMETER :: nin = 5, nout = 6
! .. Local Scalars ..
REAL (KIND=nag_wp) :: clevel, gmean, rdf, tol
INTEGER :: i, iblock, ifail, ij, irdf, j, ldc, &
lit, n, nt
CHARACTER (1) :: typ
! .. Local Arrays ..
REAL (KIND=nag_wp), ALLOCATABLE :: bmean(:), c(:,:), cil(:), ciu(:), &
ef(:), r(:), tmean(:), wk(:), y(:)
REAL (KIND=nag_wp) :: table(4,5)
INTEGER, ALLOCATABLE :: irep(:), isig(:), it(:)
CHARACTER (1) :: star(2)
! .. Intrinsic Functions ..
INTRINSIC abs
! .. Executable Statements ..
WRITE (nout,*) 'G04DBF Example Program Results'
WRITE (nout,*)
! Skip heading in data file
READ (nin,*)
! Read in the problem size
READ (nin,*) n, nt, iblock
ldc = nt
IF (nt>1) THEN
lit = n
ELSE
lit = 1
END IF
ALLOCATE (y(n),bmean(abs(iblock)),tmean(nt),irep(nt),c(ldc,nt),r(n), &
ef(nt),wk(3*nt),it(lit),cil(nt*(nt-1)/2),ciu(nt*(nt- &
1)/2),isig(nt*(nt-1)/2))
! Read in the data and plot information
READ (nin,*) y(1:n)
IF (nt>1) THEN
READ (nin,*) it(1:n)
END IF
! Read in the type of level for the CIs
READ (nin,*) typ, clevel
! Use default tolerance
tol = 0.0E0_nag_wp
! Use standard degrees of freedom
irdf = 0
! Calculate the ANOVA table
ifail = 0
CALL g04bbf(n,y,iblock,nt,it,gmean,bmean,tmean,table,4,c,ldc,irep,r,ef, &
tol,irdf,wk,ifail)
! Display results from G04BBF
WRITE (nout,*) ' ANOVA table'
WRITE (nout,*)
WRITE (nout,*) ' Source df SS MS F', &
' Prob'
WRITE (nout,*)
IF (iblock>1) THEN
WRITE (nout,99998) ' Blocks ', table(1,1:5)
END IF
WRITE (nout,99998) ' Treatments', table(2,1:5)
WRITE (nout,99998) ' Residual ', table(3,1:3)
WRITE (nout,99998) ' Total ', table(4,1:2)
WRITE (nout,*)
WRITE (nout,*) ' Treatment means'
WRITE (nout,*)
WRITE (nout,99999) tmean(1:nt)
WRITE (nout,*)
! Extract the residual degrees of freedom
rdf = table(3,1)
! Calculate simultaneous CIs
ifail = 0
CALL g04dbf(typ,nt,tmean,rdf,c,ldc,clevel,cil,ciu,isig,ifail)
! Display results from G04DBF
WRITE (nout,*) ' Simultaneous Confidence Intervals'
WRITE (nout,*)
star(2) = '*'
star(1) = ' '
ij = 0
DO i = 1, nt
DO j = 1, i - 1
ij = ij + 1
WRITE (nout,99997) i, j, cil(ij), ciu(ij), star(isig(ij)+1)
END DO
END DO
99999 FORMAT (10F8.3)
99998 FORMAT (A,3X,F3.0,2X,2(F10.1,2X),F10.3,2X,F9.4)
99997 FORMAT (2X,2I2,3X,2(F10.3,3X),A)
END PROGRAM g04dbfe
