LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dpot05 ( character  UPLO,
integer  N,
integer  NRHS,
double precision, dimension( lda, * )  A,
integer  LDA,
double precision, dimension( ldb, * )  B,
integer  LDB,
double precision, dimension( ldx, * )  X,
integer  LDX,
double precision, dimension( ldxact, * )  XACT,
integer  LDXACT,
double precision, dimension( * )  FERR,
double precision, dimension( * )  BERR,
double precision, dimension( * )  RESLTS 
)

DPOT05

Purpose:
 DPOT05 tests the error bounds from iterative refinement for the
 computed solution to a system of equations A*X = B, where A is a
 symmetric n by n matrix.

 RESLTS(1) = test of the error bound
           = norm(X - XACT) / ( norm(X) * FERR )

 A large value is returned if this ratio is not less than one.

 RESLTS(2) = residual from the iterative refinement routine
           = the maximum of BERR / ( (n+1)*EPS + (*) ), where
             (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the upper or lower triangular part of the
          symmetric matrix A is stored.
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]N
          N is INTEGER
          The number of rows of the matrices X, B, and XACT, and the
          order of the matrix A.  N >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of columns of the matrices X, B, and XACT.
          NRHS >= 0.
[in]A
          A is DOUBLE PRECISION array, dimension (LDA,N)
          The symmetric matrix A.  If UPLO = 'U', the leading n by n
          upper triangular part of A contains the upper triangular part
          of the matrix A, and the strictly lower triangular part of A
          is not referenced.  If UPLO = 'L', the leading n by n lower
          triangular part of A contains the lower triangular part of
          the matrix A, and the strictly upper triangular part of A is
          not referenced.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]B
          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
          The right hand side vectors for the system of linear
          equations.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,N).
[in]X
          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
          The computed solution vectors.  Each vector is stored as a
          column of the matrix X.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= max(1,N).
[in]XACT
          XACT is DOUBLE PRECISION array, dimension (LDX,NRHS)
          The exact solution vectors.  Each vector is stored as a
          column of the matrix XACT.
[in]LDXACT
          LDXACT is INTEGER
          The leading dimension of the array XACT.  LDXACT >= max(1,N).
[in]FERR
          FERR is DOUBLE PRECISION array, dimension (NRHS)
          The estimated forward error bounds for each solution vector
          X.  If XTRUE is the true solution, FERR bounds the magnitude
          of the largest entry in (X - XTRUE) divided by the magnitude
          of the largest entry in X.
[in]BERR
          BERR is DOUBLE PRECISION array, dimension (NRHS)
          The componentwise relative backward error of each solution
          vector (i.e., the smallest relative change in any entry of A
          or B that makes X an exact solution).
[out]RESLTS
          RESLTS is DOUBLE PRECISION array, dimension (2)
          The maximum over the NRHS solution vectors of the ratios:
          RESLTS(1) = norm(X - XACT) / ( norm(X) * FERR )
          RESLTS(2) = BERR / ( (n+1)*EPS + (*) )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 166 of file dpot05.f.

166 *
167 * -- LAPACK test routine (version 3.4.0) --
168 * -- LAPACK is a software package provided by Univ. of Tennessee, --
169 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
170 * November 2011
171 *
172 * .. Scalar Arguments ..
173  CHARACTER uplo
174  INTEGER lda, ldb, ldx, ldxact, n, nrhs
175 * ..
176 * .. Array Arguments ..
177  DOUBLE PRECISION a( lda, * ), b( ldb, * ), berr( * ), ferr( * ),
178  $ reslts( * ), x( ldx, * ), xact( ldxact, * )
179 * ..
180 *
181 * =====================================================================
182 *
183 * .. Parameters ..
184  DOUBLE PRECISION zero, one
185  parameter ( zero = 0.0d+0, one = 1.0d+0 )
186 * ..
187 * .. Local Scalars ..
188  LOGICAL upper
189  INTEGER i, imax, j, k
190  DOUBLE PRECISION axbi, diff, eps, errbnd, ovfl, tmp, unfl, xnorm
191 * ..
192 * .. External Functions ..
193  LOGICAL lsame
194  INTEGER idamax
195  DOUBLE PRECISION dlamch
196  EXTERNAL lsame, idamax, dlamch
197 * ..
198 * .. Intrinsic Functions ..
199  INTRINSIC abs, max, min
200 * ..
201 * .. Executable Statements ..
202 *
203 * Quick exit if N = 0 or NRHS = 0.
204 *
205  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
206  reslts( 1 ) = zero
207  reslts( 2 ) = zero
208  RETURN
209  END IF
210 *
211  eps = dlamch( 'Epsilon' )
212  unfl = dlamch( 'Safe minimum' )
213  ovfl = one / unfl
214  upper = lsame( uplo, 'U' )
215 *
216 * Test 1: Compute the maximum of
217 * norm(X - XACT) / ( norm(X) * FERR )
218 * over all the vectors X and XACT using the infinity-norm.
219 *
220  errbnd = zero
221  DO 30 j = 1, nrhs
222  imax = idamax( n, x( 1, j ), 1 )
223  xnorm = max( abs( x( imax, j ) ), unfl )
224  diff = zero
225  DO 10 i = 1, n
226  diff = max( diff, abs( x( i, j )-xact( i, j ) ) )
227  10 CONTINUE
228 *
229  IF( xnorm.GT.one ) THEN
230  GO TO 20
231  ELSE IF( diff.LE.ovfl*xnorm ) THEN
232  GO TO 20
233  ELSE
234  errbnd = one / eps
235  GO TO 30
236  END IF
237 *
238  20 CONTINUE
239  IF( diff / xnorm.LE.ferr( j ) ) THEN
240  errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
241  ELSE
242  errbnd = one / eps
243  END IF
244  30 CONTINUE
245  reslts( 1 ) = errbnd
246 *
247 * Test 2: Compute the maximum of BERR / ( (n+1)*EPS + (*) ), where
248 * (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
249 *
250  DO 90 k = 1, nrhs
251  DO 80 i = 1, n
252  tmp = abs( b( i, k ) )
253  IF( upper ) THEN
254  DO 40 j = 1, i
255  tmp = tmp + abs( a( j, i ) )*abs( x( j, k ) )
256  40 CONTINUE
257  DO 50 j = i + 1, n
258  tmp = tmp + abs( a( i, j ) )*abs( x( j, k ) )
259  50 CONTINUE
260  ELSE
261  DO 60 j = 1, i - 1
262  tmp = tmp + abs( a( i, j ) )*abs( x( j, k ) )
263  60 CONTINUE
264  DO 70 j = i, n
265  tmp = tmp + abs( a( j, i ) )*abs( x( j, k ) )
266  70 CONTINUE
267  END IF
268  IF( i.EQ.1 ) THEN
269  axbi = tmp
270  ELSE
271  axbi = min( axbi, tmp )
272  END IF
273  80 CONTINUE
274  tmp = berr( k ) / ( ( n+1 )*eps+( n+1 )*unfl /
275  $ max( axbi, ( n+1 )*unfl ) )
276  IF( k.EQ.1 ) THEN
277  reslts( 2 ) = tmp
278  ELSE
279  reslts( 2 ) = max( reslts( 2 ), tmp )
280  END IF
281  90 CONTINUE
282 *
283  RETURN
284 *
285 * End of DPOT05
286 *
integer function idamax(N, DX, INCX)
IDAMAX
Definition: idamax.f:53
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the caller graph for this function: