Keyword: 実対称正定値, 連立一次方程式, 誤差限界
概要
本サンプルは実対称正定値連立一次方程式の解及び誤差限界を求めるFortranによるサンプルプログラムです。 本サンプルは実対称正定値行列Aと行列Bが以下に示される場合の連立一次方程式 AX=B の解を求め、さらに条件数や誤差限界の推定値を算出して出力します。
※本サンプルはnAG Fortranライブラリに含まれるルーチン f04bdf() のExampleコードです。本サンプル及びルーチンの詳細情報は f04bdf のマニュアルページをご参照ください。
ご相談やお問い合わせはこちらまで
入力データ
(本ルーチンの詳細はf04bdf のマニュアルページを参照)| このデータをダウンロード |
F04BDF Example Program Data
4 2 :Values of N and NRHS
4.16 -3.12 0.56 -0.10
5.03 -0.83 1.18
0.76 0.34
1.18 :End of matrix A
8.70 8.30
-13.35 2.13
1.89 1.61
-4.14 5.00 :End of matrix B
- 1行目はタイトル行で読み飛ばされます。
- 3行目に行列Aの次数(n)、行列Bの列数(nrhs)を指定しています。
- 5〜8行目に行列Aの要素を指定しています。
- 10〜13行目に行列Bの要素を指定しています。
出力結果
(本ルーチンの詳細はf04bdf のマニュアルページを参照)| この出力例をダウンロード |
F04BDF Example Program Results
Solution
1 2
1 1.0000 4.0000
2 -1.0000 3.0000
3 2.0000 2.0000
4 -3.0000 1.0000
Estimate of condition number
9.7E+01
Estimate of error bound for computed solutions
1.1E-14
- 5〜8行目にxの解が出力されています。
- 11行目に行列Aの条件数の推定値が出力されています。
- 14行目に解の誤差限界の推定値が出力されています。
ソースコード
(本ルーチンの詳細はf04bdf のマニュアルページを参照)
※本サンプルソースコードは科学技術・統計計算ライブラリである「nAG Fortranライブラリ」のルーチンを呼び出します。
サンプルのコンパイル及び実行方法
| このソースコードをダウンロード |
PROGRAM f04bdfe
! F04BDF Example Program Text
! Mark 23 Release. nAG Copyright 2011.
! .. Use Statements ..
USE nag_library, ONLY : f04bdf, nag_wp, x04caf
! .. Implicit None Statement ..
IMPLICIT NONE
! .. Parameters ..
INTEGER, PARAMETER :: nin = 5, nout = 6
! .. Local Scalars ..
REAL (KIND=nag_wp) :: errbnd, rcond
INTEGER :: i, ierr, ifail, lda, ldb, n, nrhs
! .. Local Arrays ..
REAL (KIND=nag_wp), ALLOCATABLE :: a(:,:), b(:,:)
! .. Executable Statements ..
WRITE (nout,*) 'F04BDF Example Program Results'
WRITE (nout,*)
FLUSH (nout)
! Skip heading in data file
READ (nin,*)
READ (nin,*) n, nrhs
lda = n
ldb = n
ALLOCATE (a(lda,n),b(ldb,nrhs))
! Read the upper triangular part of A from data file
READ (nin,*) (a(i,i:n),i=1,n)
! Read B from data file
READ (nin,*) (b(i,1:nrhs),i=1,n)
! Solve the equations AX = B for X
! ifail: behaviour on error exit
! =0 for hard exit, =1 for quiet-soft, =-1 for noisy-soft
ifail = 1
CALL f04bdf('Upper',n,nrhs,a,lda,b,ldb,rcond,errbnd,ifail)
IF (ifail==0) THEN
! Print solution, estimate of condition number and approximate
! error bound
ierr = 0
CALL x04caf('General',' ',n,nrhs,b,ldb,'Solution',ierr)
WRITE (nout,*)
WRITE (nout,*) 'Estimate of condition number'
WRITE (nout,99999) 1.0E0_nag_wp/rcond
WRITE (nout,*)
WRITE (nout,*) 'Estimate of error bound for computed solutions'
WRITE (nout,99999) errbnd
ELSE IF (ifail==n+1) THEN
! Matrix A is numerically singular. Print estimate of
! reciprocal of condition number and solution
WRITE (nout,*)
WRITE (nout,*) 'Estimate of reciprocal of condition number'
WRITE (nout,99999) rcond
WRITE (nout,*)
FLUSH (nout)
ierr = 0
CALL x04caf('General',' ',n,nrhs,b,ldb,'Solution',ierr)
ELSE IF (ifail>0 .AND. ifail<=n) THEN
! The matrix A is not positive definite to working precision
WRITE (nout,99998) 'The leading minor of order ', ifail, &
' is not positive definite'
ELSE
WRITE (nout,99997) ifail
END IF
99999 FORMAT (6X,1P,E9.1)
99998 FORMAT (1X,A,I3,A)
99997 FORMAT (1X,' ** F04BDF returned with IFAIL = ',I5)
END PROGRAM f04bdfe
