LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sptt05 ( integer  N,
integer  NRHS,
real, dimension( * )  D,
real, dimension( * )  E,
real, dimension( ldb, * )  B,
integer  LDB,
real, dimension( ldx, * )  X,
integer  LDX,
real, dimension( ldxact, * )  XACT,
integer  LDXACT,
real, dimension( * )  FERR,
real, dimension( * )  BERR,
real, dimension( * )  RESLTS 
)

SPTT05

Purpose:
 SPTT05 tests the error bounds from iterative refinement for the
 computed solution to a system of equations A*X = B, where A is a
 symmetric tridiagonal matrix of order n.

 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(A)*abs(X) +abs(b))_i )
             and NZ = max. number of nonzeros in any row of A, plus 1
Parameters
[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]D
          D is REAL array, dimension (N)
          The n diagonal elements of the tridiagonal matrix A.
[in]E
          E is REAL array, dimension (N-1)
          The (n-1) subdiagonal elements of the tridiagonal matrix A.
[in]B
          B is REAL 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 REAL 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 REAL 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]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 / ( NZ*EPS + (*) )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 152 of file sptt05.f.

152 *
153 * -- LAPACK test routine (version 3.4.0) --
154 * -- LAPACK is a software package provided by Univ. of Tennessee, --
155 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156 * November 2011
157 *
158 * .. Scalar Arguments ..
159  INTEGER ldb, ldx, ldxact, n, nrhs
160 * ..
161 * .. Array Arguments ..
162  REAL b( ldb, * ), berr( * ), d( * ), e( * ),
163  $ ferr( * ), reslts( * ), x( ldx, * ),
164  $ xact( ldxact, * )
165 * ..
166 *
167 * =====================================================================
168 *
169 * .. Parameters ..
170  REAL zero, one
171  parameter ( zero = 0.0e+0, one = 1.0e+0 )
172 * ..
173 * .. Local Scalars ..
174  INTEGER i, imax, j, k, nz
175  REAL axbi, diff, eps, errbnd, ovfl, tmp, unfl, xnorm
176 * ..
177 * .. External Functions ..
178  INTEGER isamax
179  REAL slamch
180  EXTERNAL isamax, slamch
181 * ..
182 * .. Intrinsic Functions ..
183  INTRINSIC abs, max, min
184 * ..
185 * .. Executable Statements ..
186 *
187 * Quick exit if N = 0 or NRHS = 0.
188 *
189  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
190  reslts( 1 ) = zero
191  reslts( 2 ) = zero
192  RETURN
193  END IF
194 *
195  eps = slamch( 'Epsilon' )
196  unfl = slamch( 'Safe minimum' )
197  ovfl = one / unfl
198  nz = 4
199 *
200 * Test 1: Compute the maximum of
201 * norm(X - XACT) / ( norm(X) * FERR )
202 * over all the vectors X and XACT using the infinity-norm.
203 *
204  errbnd = zero
205  DO 30 j = 1, nrhs
206  imax = isamax( n, x( 1, j ), 1 )
207  xnorm = max( abs( x( imax, j ) ), unfl )
208  diff = zero
209  DO 10 i = 1, n
210  diff = max( diff, abs( x( i, j )-xact( i, j ) ) )
211  10 CONTINUE
212 *
213  IF( xnorm.GT.one ) THEN
214  GO TO 20
215  ELSE IF( diff.LE.ovfl*xnorm ) THEN
216  GO TO 20
217  ELSE
218  errbnd = one / eps
219  GO TO 30
220  END IF
221 *
222  20 CONTINUE
223  IF( diff / xnorm.LE.ferr( j ) ) THEN
224  errbnd = max( errbnd, ( diff / xnorm ) / ferr( j ) )
225  ELSE
226  errbnd = one / eps
227  END IF
228  30 CONTINUE
229  reslts( 1 ) = errbnd
230 *
231 * Test 2: Compute the maximum of BERR / ( NZ*EPS + (*) ), where
232 * (*) = NZ*UNFL / (min_i (abs(A)*abs(X) +abs(b))_i )
233 *
234  DO 50 k = 1, nrhs
235  IF( n.EQ.1 ) THEN
236  axbi = abs( b( 1, k ) ) + abs( d( 1 )*x( 1, k ) )
237  ELSE
238  axbi = abs( b( 1, k ) ) + abs( d( 1 )*x( 1, k ) ) +
239  $ abs( e( 1 )*x( 2, k ) )
240  DO 40 i = 2, n - 1
241  tmp = abs( b( i, k ) ) + abs( e( i-1 )*x( i-1, k ) ) +
242  $ abs( d( i )*x( i, k ) ) + abs( e( i )*x( i+1, k ) )
243  axbi = min( axbi, tmp )
244  40 CONTINUE
245  tmp = abs( b( n, k ) ) + abs( e( n-1 )*x( n-1, k ) ) +
246  $ abs( d( n )*x( n, k ) )
247  axbi = min( axbi, tmp )
248  END IF
249  tmp = berr( k ) / ( nz*eps+nz*unfl / max( axbi, nz*unfl ) )
250  IF( k.EQ.1 ) THEN
251  reslts( 2 ) = tmp
252  ELSE
253  reslts( 2 ) = max( reslts( 2 ), tmp )
254  END IF
255  50 CONTINUE
256 *
257  RETURN
258 *
259 * End of SPTT05
260 *
integer function isamax(N, SX, INCX)
ISAMAX
Definition: isamax.f:53
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69

Here is the caller graph for this function: