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

◆ dget07()

subroutine dget07 ( character  trans,
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,
logical  chkferr,
double precision, dimension( * )  berr,
double precision, dimension( * )  reslts 
)

DGET07

Purpose:
 DGET07 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 DOUBLE PRECISION 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 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]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.

Definition at line 163 of file dget07.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 TRANS
172 LOGICAL CHKFERR
173 INTEGER LDA, LDB, LDX, LDXACT, N, NRHS
174* ..
175* .. Array Arguments ..
176 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), BERR( * ), FERR( * ),
177 $ RESLTS( * ), X( LDX, * ), 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 NOTRAN
188 INTEGER I, IMAX, J, K
189 DOUBLE PRECISION AXBI, DIFF, EPS, ERRBND, OVFL, TMP, UNFL, XNORM
190* ..
191* .. External Functions ..
192 LOGICAL LSAME
193 INTEGER IDAMAX
194 DOUBLE PRECISION DLAMCH
195 EXTERNAL lsame, idamax, dlamch
196* ..
197* .. Intrinsic Functions ..
198 INTRINSIC abs, max, min
199* ..
200* .. Executable Statements ..
201*
202* Quick exit if N = 0 or NRHS = 0.
203*
204 IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
205 reslts( 1 ) = zero
206 reslts( 2 ) = zero
207 RETURN
208 END IF
209*
210 eps = dlamch( 'Epsilon' )
211 unfl = dlamch( 'Safe minimum' )
212 ovfl = one / unfl
213 notran = lsame( trans, 'N' )
214*
215* Test 1: Compute the maximum of
216* norm(X - XACT) / ( norm(X) * FERR )
217* over all the vectors X and XACT using the infinity-norm.
218*
219 errbnd = zero
220 IF( chkferr ) THEN
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 END IF
246 reslts( 1 ) = errbnd
247*
248* Test 2: Compute the maximum of BERR / ( (n+1)*EPS + (*) ), where
249* (*) = (n+1)*UNFL / (min_i (abs(op(A))*abs(X) +abs(b))_i )
250*
251 DO 70 k = 1, nrhs
252 DO 60 i = 1, n
253 tmp = abs( b( i, k ) )
254 IF( notran ) THEN
255 DO 40 j = 1, n
256 tmp = tmp + abs( a( i, j ) )*abs( x( j, k ) )
257 40 CONTINUE
258 ELSE
259 DO 50 j = 1, n
260 tmp = tmp + abs( a( j, i ) )*abs( x( j, k ) )
261 50 CONTINUE
262 END IF
263 IF( i.EQ.1 ) THEN
264 axbi = tmp
265 ELSE
266 axbi = min( axbi, tmp )
267 END IF
268 60 CONTINUE
269 tmp = berr( k ) / ( ( n+1 )*eps+( n+1 )*unfl /
270 $ max( axbi, ( n+1 )*unfl ) )
271 IF( k.EQ.1 ) THEN
272 reslts( 2 ) = tmp
273 ELSE
274 reslts( 2 ) = max( reslts( 2 ), tmp )
275 END IF
276 70 CONTINUE
277*
278 RETURN
279*
280* End of DGET07
281*
integer function idamax(n, dx, incx)
IDAMAX
Definition idamax.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: