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

◆ zgtt02()

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

ZGTT02

Purpose:
 ZGTT02 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.
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)
[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 COMPLEX*16 array, dimension (N-1)
          The (n-1) sub-diagonal elements of A.
[in]D
          D is COMPLEX*16 array, dimension (N)
          The diagonal elements of A.
[in]DU
          DU is COMPLEX*16 array, dimension (N-1)
          The (n-1) super-diagonal elements of A.
[in]X
          X is COMPLEX*16 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 COMPLEX*16 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 122 of file zgtt02.f.

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