LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dgtt05 ( character  TRANS,
integer  N,
integer  NRHS,
double precision, dimension( * )  DL,
double precision, dimension( * )  D,
double precision, dimension( * )  DU,
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 
)

DGTT05

Purpose:
 DGTT05 tests the error bounds from iterative refinement for the
 computed solution to a system of equations A*X = B, where A is a
 general tridiagonal matrix of order n 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 / ( NZ*EPS + (*) ), where
             (*) = NZ*UNFL / (min_i (abs(op(A))*abs(X) +abs(b))_i )
             and NZ = max. number of nonzeros in any row of A, plus 1
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]DL
          DL is DOUBLE PRECISION array, dimension (N-1)
          The (n-1) sub-diagonal elements of A.
[in]D
          D is DOUBLE PRECISION array, dimension (N)
          The diagonal elements of A.
[in]DU
          DU is DOUBLE PRECISION array, dimension (N-1)
          The (n-1) super-diagonal elements of A.
[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 / ( NZ*EPS + (*) )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 167 of file dgtt05.f.

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