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

◆ dgtt02()

subroutine dgtt02 ( character  trans,
integer  n,
integer  nrhs,
double precision, dimension( * )  dl,
double precision, dimension( * )  d,
double precision, dimension( * )  du,
double precision, dimension( ldx, * )  x,
integer  ldx,
double precision, dimension( ldb, * )  b,
integer  ldb,
double precision  resid 
)

DGTT02

Purpose:
 DGTT02 computes the residual for the solution to a tridiagonal
 system of equations:
    RESID = norm(B - op(A)*X) / (norm(op(A)) * norm(X) * EPS),
 where EPS is the machine epsilon.
 The norm used is the 1-norm.
Parameters
[in]TRANS
          TRANS is CHARACTER
          Specifies the form of the residual.
          = 'N':  B - A    * X  (No transpose)
          = 'T':  B - A**T * X  (Transpose)
          = 'C':  B - A**H * X  (Conjugate transpose = Transpose)
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[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]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]X
          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
          The computed solution vectors X.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= max(1,N).
[in,out]B
          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
          On entry, the right hand side vectors for the system of
          linear equations.
          On exit, B is overwritten with the difference B - op(A)*X.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,N).
[out]RESID
          RESID is DOUBLE PRECISION
          norm(B - op(A)*X) / (norm(op(A)) * norm(X) * EPS)
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 123 of file dgtt02.f.

125*
126* -- LAPACK test routine --
127* -- LAPACK is a software package provided by Univ. of Tennessee, --
128* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130* .. Scalar Arguments ..
131 CHARACTER TRANS
132 INTEGER LDB, LDX, N, NRHS
133 DOUBLE PRECISION RESID
134* ..
135* .. Array Arguments ..
136 DOUBLE PRECISION B( LDB, * ), D( * ), DL( * ), DU( * ),
137 $ X( LDX, * )
138* ..
139*
140* =====================================================================
141*
142* .. Parameters ..
143 DOUBLE PRECISION ONE, ZERO
144 parameter( one = 1.0d+0, zero = 0.0d+0 )
145* ..
146* .. Local Scalars ..
147 INTEGER J
148 DOUBLE PRECISION ANORM, BNORM, EPS, XNORM
149* ..
150* .. External Functions ..
151 LOGICAL LSAME
152 DOUBLE PRECISION DASUM, DLAMCH, DLANGT
153 EXTERNAL lsame, dasum, dlamch, dlangt
154* ..
155* .. External Subroutines ..
156 EXTERNAL dlagtm
157* ..
158* .. Intrinsic Functions ..
159 INTRINSIC max
160* ..
161* .. Executable Statements ..
162*
163* Quick exit if N = 0 or NRHS = 0
164*
165 resid = zero
166 IF( n.LE.0 .OR. nrhs.EQ.0 )
167 $ RETURN
168*
169* Compute the maximum over the number of right hand sides of
170* norm(B - op(A)*X) / ( norm(op(A)) * norm(X) * EPS ).
171*
172 IF( lsame( trans, 'N' ) ) THEN
173 anorm = dlangt( '1', n, dl, d, du )
174 ELSE
175 anorm = dlangt( 'I', n, dl, d, du )
176 END IF
177*
178* Exit with RESID = 1/EPS if ANORM = 0.
179*
180 eps = dlamch( 'Epsilon' )
181 IF( anorm.LE.zero ) THEN
182 resid = one / eps
183 RETURN
184 END IF
185*
186* Compute B - op(A)*X and store in B.
187*
188 CALL dlagtm( trans, n, nrhs, -one, dl, d, du, x, ldx, one, b,
189 $ ldb )
190*
191 DO 10 j = 1, nrhs
192 bnorm = dasum( n, b( 1, j ), 1 )
193 xnorm = dasum( n, x( 1, j ), 1 )
194 IF( xnorm.LE.zero ) THEN
195 resid = one / eps
196 ELSE
197 resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
198 END IF
199 10 CONTINUE
200*
201 RETURN
202*
203* End of DGTT02
204*
double precision function dasum(n, dx, incx)
DASUM
Definition dasum.f:71
subroutine dlagtm(trans, n, nrhs, alpha, dl, d, du, x, ldx, beta, b, ldb)
DLAGTM performs a matrix-matrix product of the form C = αAB+βC, where A is a tridiagonal matrix,...
Definition dlagtm.f:145
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlangt(norm, n, dl, d, du)
DLANGT returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition dlangt.f:106
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: