LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zpot05()

subroutine zpot05 ( character  uplo,
integer  n,
integer  nrhs,
complex*16, dimension( lda, * )  a,
integer  lda,
complex*16, dimension( ldb, * )  b,
integer  ldb,
complex*16, dimension( ldx, * )  x,
integer  ldx,
complex*16, dimension( ldxact, * )  xact,
integer  ldxact,
double precision, dimension( * )  ferr,
double precision, dimension( * )  berr,
double precision, dimension( * )  reslts 
)

ZPOT05

Purpose:
 ZPOT05 tests the error bounds from iterative refinement for the
 computed solution to a system of equations A*X = B, where A is a
 Hermitian 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
          Hermitian 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 COMPLEX*16 array, dimension (LDA,N)
          The Hermitian 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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.

Definition at line 163 of file zpot05.f.

165*
166* -- LAPACK test routine --
167* -- LAPACK is a software package provided by Univ. of Tennessee, --
168* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
169*
170* .. Scalar Arguments ..
171 CHARACTER UPLO
172 INTEGER LDA, LDB, LDX, LDXACT, N, NRHS
173* ..
174* .. Array Arguments ..
175 DOUBLE PRECISION BERR( * ), FERR( * ), RESLTS( * )
176 COMPLEX*16 A( LDA, * ), B( LDB, * ), X( LDX, * ),
177 $ XACT( LDXACT, * )
178* ..
179*
180* =====================================================================
181*
182* .. Parameters ..
183 DOUBLE PRECISION ZERO, ONE
184 parameter( zero = 0.0d+0, one = 1.0d+0 )
185* ..
186* .. Local Scalars ..
187 LOGICAL UPPER
188 INTEGER I, IMAX, J, K
189 DOUBLE PRECISION AXBI, DIFF, EPS, ERRBND, OVFL, TMP, UNFL, XNORM
190 COMPLEX*16 ZDUM
191* ..
192* .. External Functions ..
193 LOGICAL LSAME
194 INTEGER IZAMAX
195 DOUBLE PRECISION DLAMCH
196 EXTERNAL lsame, izamax, dlamch
197* ..
198* .. Intrinsic Functions ..
199 INTRINSIC abs, dble, dimag, max, min
200* ..
201* .. Statement Functions ..
202 DOUBLE PRECISION CABS1
203* ..
204* .. Statement Function definitions ..
205 cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
206* ..
207* .. Executable Statements ..
208*
209* Quick exit if N = 0 or NRHS = 0.
210*
211 IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
212 reslts( 1 ) = zero
213 reslts( 2 ) = zero
214 RETURN
215 END IF
216*
217 eps = dlamch( 'Epsilon' )
218 unfl = dlamch( 'Safe minimum' )
219 ovfl = one / unfl
220 upper = lsame( uplo, 'U' )
221*
222* Test 1: Compute the maximum of
223* norm(X - XACT) / ( norm(X) * FERR )
224* over all the vectors X and XACT using the infinity-norm.
225*
226 errbnd = zero
227 DO 30 j = 1, nrhs
228 imax = izamax( n, x( 1, j ), 1 )
229 xnorm = max( cabs1( x( imax, j ) ), unfl )
230 diff = zero
231 DO 10 i = 1, n
232 diff = max( diff, cabs1( x( i, j )-xact( i, j ) ) )
233 10 CONTINUE
234*
235 IF( xnorm.GT.one ) THEN
236 GO TO 20
237 ELSE IF( diff.LE.ovfl*xnorm ) THEN
238 GO TO 20
239 ELSE
240 errbnd = one / eps
241 GO TO 30
242 END IF
243*
244 20 CONTINUE
245 IF( diff / xnorm.LE.ferr( j ) ) THEN
246 errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
247 ELSE
248 errbnd = one / eps
249 END IF
250 30 CONTINUE
251 reslts( 1 ) = errbnd
252*
253* Test 2: Compute the maximum of BERR / ( (n+1)*EPS + (*) ), where
254* (*) = (n+1)*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
255*
256 DO 90 k = 1, nrhs
257 DO 80 i = 1, n
258 tmp = cabs1( b( i, k ) )
259 IF( upper ) THEN
260 DO 40 j = 1, i - 1
261 tmp = tmp + cabs1( a( j, i ) )*cabs1( x( j, k ) )
262 40 CONTINUE
263 tmp = tmp + abs( dble( a( i, i ) ) )*cabs1( x( i, k ) )
264 DO 50 j = i + 1, n
265 tmp = tmp + cabs1( a( i, j ) )*cabs1( x( j, k ) )
266 50 CONTINUE
267 ELSE
268 DO 60 j = 1, i - 1
269 tmp = tmp + cabs1( a( i, j ) )*cabs1( x( j, k ) )
270 60 CONTINUE
271 tmp = tmp + abs( dble( a( i, i ) ) )*cabs1( x( i, k ) )
272 DO 70 j = i + 1, n
273 tmp = tmp + cabs1( a( j, i ) )*cabs1( x( j, k ) )
274 70 CONTINUE
275 END IF
276 IF( i.EQ.1 ) THEN
277 axbi = tmp
278 ELSE
279 axbi = min( axbi, tmp )
280 END IF
281 80 CONTINUE
282 tmp = berr( k ) / ( ( n+1 )*eps+( n+1 )*unfl /
283 $ max( axbi, ( n+1 )*unfl ) )
284 IF( k.EQ.1 ) THEN
285 reslts( 2 ) = tmp
286 ELSE
287 reslts( 2 ) = max( reslts( 2 ), tmp )
288 END IF
289 90 CONTINUE
290*
291 RETURN
292*
293* End of ZPOT05
294*
integer function izamax(n, zx, incx)
IZAMAX
Definition izamax.f:71
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the caller graph for this function: