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

◆ dptt05()

subroutine dptt05 ( integer  n,
integer  nrhs,
double precision, dimension( * )  d,
double precision, dimension( * )  e,
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 
)

DPTT05

Purpose:
 DPTT05 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 DOUBLE PRECISION array, dimension (N)
          The n diagonal elements of the tridiagonal matrix A.
[in]E
          E is DOUBLE PRECISION array, dimension (N-1)
          The (n-1) subdiagonal elements of the tridiagonal matrix 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.

Definition at line 148 of file dptt05.f.

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