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

◆ sptt02()

subroutine sptt02 ( integer  n,
integer  nrhs,
real, dimension( * )  d,
real, dimension( * )  e,
real, dimension( ldx, * )  x,
integer  ldx,
real, dimension( ldb, * )  b,
integer  ldb,
real  resid 
)

SPTT02

Purpose:
 SPTT02 computes the residual for the solution to a symmetric
 tridiagonal system of equations:
    RESID = norm(B - A*X) / (norm(A) * norm(X) * EPS),
 where EPS is the machine epsilon.
Parameters
[in]N
          N is INTEGER
          The order of the matrix A.
[in]NRHS
          NRHS is INTEGER
          The number of right hand sides, i.e., the number of columns
          of the matrices B and X.  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]X
          X is REAL array, dimension (LDX,NRHS)
          The n by nrhs matrix of solution vectors X.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= max(1,N).
[in,out]B
          B is REAL array, dimension (LDB,NRHS)
          On entry, the n by nrhs matrix of right hand side vectors B.
          On exit, B is overwritten with the difference B - A*X.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,N).
[out]RESID
          RESID is REAL
          norm(B - A*X) / (norm(A) * norm(X) * EPS)
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 103 of file sptt02.f.

104*
105* -- LAPACK test routine --
106* -- LAPACK is a software package provided by Univ. of Tennessee, --
107* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
108*
109* .. Scalar Arguments ..
110 INTEGER LDB, LDX, N, NRHS
111 REAL RESID
112* ..
113* .. Array Arguments ..
114 REAL B( LDB, * ), D( * ), E( * ), X( LDX, * )
115* ..
116*
117* =====================================================================
118*
119* .. Parameters ..
120 REAL ONE, ZERO
121 parameter( one = 1.0e+0, zero = 0.0e+0 )
122* ..
123* .. Local Scalars ..
124 INTEGER J
125 REAL ANORM, BNORM, EPS, XNORM
126* ..
127* .. External Functions ..
128 REAL SASUM, SLAMCH, SLANST
129 EXTERNAL sasum, slamch, slanst
130* ..
131* .. Intrinsic Functions ..
132 INTRINSIC max
133* ..
134* .. External Subroutines ..
135 EXTERNAL slaptm
136* ..
137* .. Executable Statements ..
138*
139* Quick return if possible
140*
141 IF( n.LE.0 ) THEN
142 resid = zero
143 RETURN
144 END IF
145*
146* Compute the 1-norm of the tridiagonal matrix A.
147*
148 anorm = slanst( '1', n, d, e )
149*
150* Exit with RESID = 1/EPS if ANORM = 0.
151*
152 eps = slamch( 'Epsilon' )
153 IF( anorm.LE.zero ) THEN
154 resid = one / eps
155 RETURN
156 END IF
157*
158* Compute B - A*X.
159*
160 CALL slaptm( n, nrhs, -one, d, e, x, ldx, one, b, ldb )
161*
162* Compute the maximum over the number of right hand sides of
163* norm(B - A*X) / ( norm(A) * norm(X) * EPS ).
164*
165 resid = zero
166 DO 10 j = 1, nrhs
167 bnorm = sasum( n, b( 1, j ), 1 )
168 xnorm = sasum( n, x( 1, j ), 1 )
169 IF( xnorm.LE.zero ) THEN
170 resid = one / eps
171 ELSE
172 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
173 END IF
174 10 CONTINUE
175*
176 RETURN
177*
178* End of SPTT02
179*
real function sasum(n, sx, incx)
SASUM
Definition sasum.f:72
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function slanst(norm, n, d, e)
SLANST returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition slanst.f:100
subroutine slaptm(n, nrhs, alpha, d, e, x, ldx, beta, b, ldb)
SLAPTM
Definition slaptm.f:116
Here is the call graph for this function:
Here is the caller graph for this function: