LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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(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 INTEGTER
          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(A) * norm(X) * EPS)
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 126 of file zgtt02.f.

126 *
127 * -- LAPACK test routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * November 2011
131 *
132 * .. Scalar Arguments ..
133  CHARACTER trans
134  INTEGER ldb, ldx, n, nrhs
135  DOUBLE PRECISION resid
136 * ..
137 * .. Array Arguments ..
138  COMPLEX*16 b( ldb, * ), d( * ), dl( * ), du( * ),
139  $ x( ldx, * )
140 * ..
141 *
142 * =====================================================================
143 *
144 * .. Parameters ..
145  DOUBLE PRECISION one, zero
146  parameter ( one = 1.0d+0, zero = 0.0d+0 )
147 * ..
148 * .. Local Scalars ..
149  INTEGER j
150  DOUBLE PRECISION anorm, bnorm, eps, xnorm
151 * ..
152 * .. External Functions ..
153  LOGICAL lsame
154  DOUBLE PRECISION dlamch, dzasum, zlangt
155  EXTERNAL lsame, dlamch, dzasum, zlangt
156 * ..
157 * .. External Subroutines ..
158  EXTERNAL zlagtm
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC max
162 * ..
163 * .. Executable Statements ..
164 *
165 * Quick exit if N = 0 or NRHS = 0
166 *
167  resid = zero
168  IF( n.LE.0 .OR. nrhs.EQ.0 )
169  $ RETURN
170 *
171 * Compute the maximum over the number of right hand sides of
172 * norm(B - op(A)*X) / ( norm(A) * norm(X) * EPS ).
173 *
174  IF( lsame( trans, 'N' ) ) THEN
175  anorm = zlangt( '1', n, dl, d, du )
176  ELSE
177  anorm = zlangt( 'I', n, dl, d, du )
178  END IF
179 *
180 * Exit with RESID = 1/EPS if ANORM = 0.
181 *
182  eps = dlamch( 'Epsilon' )
183  IF( anorm.LE.zero ) THEN
184  resid = one / eps
185  RETURN
186  END IF
187 *
188 * Compute B - op(A)*X.
189 *
190  CALL zlagtm( trans, n, nrhs, -one, dl, d, du, x, ldx, one, b,
191  $ ldb )
192 *
193  DO 10 j = 1, nrhs
194  bnorm = dzasum( n, b( 1, j ), 1 )
195  xnorm = dzasum( n, x( 1, j ), 1 )
196  IF( xnorm.LE.zero ) THEN
197  resid = one / eps
198  ELSE
199  resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
200  END IF
201  10 CONTINUE
202 *
203  RETURN
204 *
205 * End of ZGTT02
206 *
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:147
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
double precision function dzasum(N, ZX, INCX)
DZASUM
Definition: dzasum.f:54
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:108
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: