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

◆ cget07()

subroutine cget07 ( character  trans,
integer  n,
integer  nrhs,
complex, dimension( lda, * )  a,
integer  lda,
complex, dimension( ldb, * )  b,
integer  ldb,
complex, dimension( ldx, * )  x,
integer  ldx,
complex, dimension( ldxact, * )  xact,
integer  ldxact,
real, dimension( * )  ferr,
logical  chkferr,
real, dimension( * )  berr,
real, dimension( * )  reslts 
)

CGET07

Purpose:
 CGET07 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 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 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 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 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 REAL 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 REAL 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 REAL 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 164 of file cget07.f.

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