LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zget07 ( character  TRANS,
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,
logical  CHKFERR,
double precision, dimension( * )  BERR,
double precision, dimension( * )  RESLTS 
)

ZGET07

Purpose:
 ZGET07 tests the error bounds from iterative refinement for the
 computed solution to a system of equations op(A)*X = B, where A is a
 general n by n matrix and op(A) = A or A**T, depending on TRANS.

 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(op(A))*abs(X) +abs(b))_i )
Parameters
[in]TRANS
          TRANS is CHARACTER*1
          Specifies the form of the system of equations.
          = 'N':  A * X = B     (No transpose)
          = 'T':  A**T * X = B  (Transpose)
          = 'C':  A**H * X = B  (Conjugate transpose = Transpose)
[in]N
          N is INTEGER
          The number of rows of the matrices X and XACT.  N >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of columns of the matrices X and XACT.  NRHS >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The original n by n matrix A.
[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]CHKFERR
          CHKFERR is LOGICAL
          Set to .TRUE. to check FERR, .FALSE. not to check FERR.
          When the test system is ill-conditioned, the "true"
          solution in XACT may be incorrect.
[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 168 of file zget07.f.

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

Here is the caller graph for this function: