LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ztrt02 ( character  UPLO,
character  TRANS,
character  DIAG,
integer  N,
integer  NRHS,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( ldx, * )  X,
integer  LDX,
complex*16, dimension( ldb, * )  B,
integer  LDB,
complex*16, dimension( * )  WORK,
double precision, dimension( * )  RWORK,
double precision  RESID 
)

ZTRT02

Purpose:
 ZTRT02 computes the residual for the computed solution to a
 triangular system of linear equations  A*x = b,  A**T *x = b,
 or A**H *x = b.  Here A is a triangular matrix, A**T is the transpose
 of A, A**H is the conjugate transpose of A, and x and b are N by NRHS
 matrices.  The test ratio is the maximum over the number of right
 hand sides of
    norm(b - op(A)*x) / ( norm(op(A)) * norm(x) * EPS ),
 where op(A) denotes A, A**T, or A**H, and EPS is the machine epsilon.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the matrix A is upper or lower triangular.
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]TRANS
          TRANS is CHARACTER*1
          Specifies the operation applied to A.
          = 'N':  A *x = b     (No transpose)
          = 'T':  A**T *x = b  (Transpose)
          = 'C':  A**H *x = b  (Conjugate transpose)
[in]DIAG
          DIAG is CHARACTER*1
          Specifies whether or not the matrix A is unit triangular.
          = 'N':  Non-unit triangular
          = 'U':  Unit triangular
[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 X and B.  NRHS >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The triangular matrix A.  If UPLO = 'U', the leading n by n
          upper triangular part of the array A contains the upper
          triangular matrix, and the strictly lower triangular part of
          A is not referenced.  If UPLO = 'L', the leading n by n lower
          triangular part of the array A contains the lower triangular
          matrix, and the strictly upper triangular part of A is not
          referenced.  If DIAG = 'U', the diagonal elements of A are
          also not referenced and are assumed to be 1.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]X
          X is COMPLEX*16 array, dimension (LDX,NRHS)
          The computed solution vectors for the system of linear
          equations.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.  LDX >= max(1,N).
[in]B
          B is COMPLEX*16 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).
[out]WORK
          WORK is COMPLEX*16 array, dimension (N)
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N)
[out]RESID
          RESID is DOUBLE PRECISION
          The maximum over the number of right hand sides of
          norm(op(A)*x - b) / ( norm(op(A)) * norm(x) * EPS ).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 159 of file ztrt02.f.

159 *
160 * -- LAPACK test routine (version 3.4.0) --
161 * -- LAPACK is a software package provided by Univ. of Tennessee, --
162 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
163 * November 2011
164 *
165 * .. Scalar Arguments ..
166  CHARACTER diag, trans, uplo
167  INTEGER lda, ldb, ldx, n, nrhs
168  DOUBLE PRECISION resid
169 * ..
170 * .. Array Arguments ..
171  DOUBLE PRECISION rwork( * )
172  COMPLEX*16 a( lda, * ), b( ldb, * ), work( * ),
173  $ x( ldx, * )
174 * ..
175 *
176 * =====================================================================
177 *
178 * .. Parameters ..
179  DOUBLE PRECISION zero, one
180  parameter ( zero = 0.0d+0, one = 1.0d+0 )
181 * ..
182 * .. Local Scalars ..
183  INTEGER j
184  DOUBLE PRECISION anorm, bnorm, eps, xnorm
185 * ..
186 * .. External Functions ..
187  LOGICAL lsame
188  DOUBLE PRECISION dlamch, dzasum, zlantr
189  EXTERNAL lsame, dlamch, dzasum, zlantr
190 * ..
191 * .. External Subroutines ..
192  EXTERNAL zaxpy, zcopy, ztrmv
193 * ..
194 * .. Intrinsic Functions ..
195  INTRINSIC dcmplx, max
196 * ..
197 * .. Executable Statements ..
198 *
199 * Quick exit if N = 0 or NRHS = 0
200 *
201  IF( n.LE.0 .OR. nrhs.LE.0 ) THEN
202  resid = zero
203  RETURN
204  END IF
205 *
206 * Compute the 1-norm of A or A**H.
207 *
208  IF( lsame( trans, 'N' ) ) THEN
209  anorm = zlantr( '1', uplo, diag, n, n, a, lda, rwork )
210  ELSE
211  anorm = zlantr( 'I', uplo, diag, n, n, a, lda, rwork )
212  END IF
213 *
214 * Exit with RESID = 1/EPS if ANORM = 0.
215 *
216  eps = dlamch( 'Epsilon' )
217  IF( anorm.LE.zero ) THEN
218  resid = one / eps
219  RETURN
220  END IF
221 *
222 * Compute the maximum over the number of right hand sides of
223 * norm(op(A)*x - b) / ( norm(op(A)) * norm(x) * EPS )
224 *
225  resid = zero
226  DO 10 j = 1, nrhs
227  CALL zcopy( n, x( 1, j ), 1, work, 1 )
228  CALL ztrmv( uplo, trans, diag, n, a, lda, work, 1 )
229  CALL zaxpy( n, dcmplx( -one ), b( 1, j ), 1, work, 1 )
230  bnorm = dzasum( n, work, 1 )
231  xnorm = dzasum( n, x( 1, j ), 1 )
232  IF( xnorm.LE.zero ) THEN
233  resid = one / eps
234  ELSE
235  resid = max( resid, ( ( bnorm / anorm ) / xnorm ) / eps )
236  END IF
237  10 CONTINUE
238 *
239  RETURN
240 *
241 * End of ZTRT02
242 *
subroutine zcopy(N, ZX, INCX, ZY, INCY)
ZCOPY
Definition: zcopy.f:52
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
double precision function zlantr(NORM, UPLO, DIAG, M, N, A, LDA, WORK)
ZLANTR returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a trapezoidal or triangular matrix.
Definition: zlantr.f:144
double precision function dzasum(N, ZX, INCX)
DZASUM
Definition: dzasum.f:54
subroutine ztrmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
ZTRMV
Definition: ztrmv.f:149
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zaxpy(N, ZA, ZX, INCX, ZY, INCY)
ZAXPY
Definition: zaxpy.f:53

Here is the call graph for this function:

Here is the caller graph for this function: