LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ztrt01 ( character  UPLO,
character  DIAG,
integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( ldainv, * )  AINV,
integer  LDAINV,
double precision  RCOND,
double precision, dimension( * )  RWORK,
double precision  RESID 
)

ZTRT01

Purpose:
 ZTRT01 computes the residual for a triangular matrix A times its
 inverse:
    RESID = norm( A*AINV - I ) / ( N * norm(A) * norm(AINV) * EPS ),
 where 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]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]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]AINV
          AINV is COMPLEX*16 array, dimension (LDAINV,N)
          On entry, the (triangular) inverse of the matrix A, in the
          same storage format as A.
          On exit, the contents of AINV are destroyed.
[in]LDAINV
          LDAINV is INTEGER
          The leading dimension of the array AINV.  LDAINV >= max(1,N).
[out]RCOND
          RCOND is DOUBLE PRECISION
          The reciprocal condition number of A, computed as
          1/(norm(A) * norm(AINV)).
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N)
[out]RESID
          RESID is DOUBLE PRECISION
          norm(A*AINV - I) / ( N * norm(A) * norm(AINV) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 127 of file ztrt01.f.

127 *
128 * -- LAPACK test routine (version 3.4.0) --
129 * -- LAPACK is a software package provided by Univ. of Tennessee, --
130 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * November 2011
132 *
133 * .. Scalar Arguments ..
134  CHARACTER diag, uplo
135  INTEGER lda, ldainv, n
136  DOUBLE PRECISION rcond, resid
137 * ..
138 * .. Array Arguments ..
139  DOUBLE PRECISION rwork( * )
140  COMPLEX*16 a( lda, * ), ainv( ldainv, * )
141 * ..
142 *
143 * =====================================================================
144 *
145 * .. Parameters ..
146  DOUBLE PRECISION zero, one
147  parameter ( zero = 0.0d+0, one = 1.0d+0 )
148 * ..
149 * .. Local Scalars ..
150  INTEGER j
151  DOUBLE PRECISION ainvnm, anorm, eps
152 * ..
153 * .. External Functions ..
154  LOGICAL lsame
155  DOUBLE PRECISION dlamch, zlantr
156  EXTERNAL lsame, dlamch, zlantr
157 * ..
158 * .. External Subroutines ..
159  EXTERNAL ztrmv
160 * ..
161 * .. Intrinsic Functions ..
162  INTRINSIC dble
163 * ..
164 * .. Executable Statements ..
165 *
166 * Quick exit if N = 0
167 *
168  IF( n.LE.0 ) THEN
169  rcond = one
170  resid = zero
171  RETURN
172  END IF
173 *
174 * Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
175 *
176  eps = dlamch( 'Epsilon' )
177  anorm = zlantr( '1', uplo, diag, n, n, a, lda, rwork )
178  ainvnm = zlantr( '1', uplo, diag, n, n, ainv, ldainv, rwork )
179  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
180  rcond = zero
181  resid = one / eps
182  RETURN
183  END IF
184  rcond = ( one / anorm ) / ainvnm
185 *
186 * Set the diagonal of AINV to 1 if AINV has unit diagonal.
187 *
188  IF( lsame( diag, 'U' ) ) THEN
189  DO 10 j = 1, n
190  ainv( j, j ) = one
191  10 CONTINUE
192  END IF
193 *
194 * Compute A * AINV, overwriting AINV.
195 *
196  IF( lsame( uplo, 'U' ) ) THEN
197  DO 20 j = 1, n
198  CALL ztrmv( 'Upper', 'No transpose', diag, j, a, lda,
199  $ ainv( 1, j ), 1 )
200  20 CONTINUE
201  ELSE
202  DO 30 j = 1, n
203  CALL ztrmv( 'Lower', 'No transpose', diag, n-j+1, a( j, j ),
204  $ lda, ainv( j, j ), 1 )
205  30 CONTINUE
206  END IF
207 *
208 * Subtract 1 from each diagonal element to form A*AINV - I.
209 *
210  DO 40 j = 1, n
211  ainv( j, j ) = ainv( j, j ) - one
212  40 CONTINUE
213 *
214 * Compute norm(A*AINV - I) / (N * norm(A) * norm(AINV) * EPS)
215 *
216  resid = zlantr( '1', uplo, 'Non-unit', n, n, ainv, ldainv, rwork )
217 *
218  resid = ( ( resid*rcond ) / dble( n ) ) / eps
219 *
220  RETURN
221 *
222 * End of ZTRT01
223 *
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
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

Here is the call graph for this function:

Here is the caller graph for this function: