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

◆ ctrt01()

subroutine ctrt01 ( character  uplo,
character  diag,
integer  n,
complex, dimension( lda, * )  a,
integer  lda,
complex, dimension( ldainv, * )  ainv,
integer  ldainv,
real  rcond,
real, dimension( * )  rwork,
real  resid 
)

CTRT01

Purpose:
 CTRT01 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 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 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 REAL
          The reciprocal condition number of A, computed as
          1/(norm(A) * norm(AINV)).
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]RESID
          RESID is REAL
          norm(A*AINV - I) / ( N * norm(A) * norm(AINV) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 123 of file ctrt01.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 DIAG, UPLO
132 INTEGER LDA, LDAINV, N
133 REAL RCOND, RESID
134* ..
135* .. Array Arguments ..
136 REAL RWORK( * )
137 COMPLEX A( LDA, * ), AINV( LDAINV, * )
138* ..
139*
140* =====================================================================
141*
142* .. Parameters ..
143 REAL ZERO, ONE
144 parameter( zero = 0.0e+0, one = 1.0e+0 )
145* ..
146* .. Local Scalars ..
147 INTEGER J
148 REAL AINVNM, ANORM, EPS
149* ..
150* .. External Functions ..
151 LOGICAL LSAME
152 REAL CLANTR, SLAMCH
153 EXTERNAL lsame, clantr, slamch
154* ..
155* .. External Subroutines ..
156 EXTERNAL ctrmv
157* ..
158* .. Intrinsic Functions ..
159 INTRINSIC real
160* ..
161* .. Executable Statements ..
162*
163* Quick exit if N = 0
164*
165 IF( n.LE.0 ) THEN
166 rcond = one
167 resid = zero
168 RETURN
169 END IF
170*
171* Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
172*
173 eps = slamch( 'Epsilon' )
174 anorm = clantr( '1', uplo, diag, n, n, a, lda, rwork )
175 ainvnm = clantr( '1', uplo, diag, n, n, ainv, ldainv, rwork )
176 IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
177 rcond = zero
178 resid = one / eps
179 RETURN
180 END IF
181 rcond = ( one / anorm ) / ainvnm
182*
183* Set the diagonal of AINV to 1 if AINV has unit diagonal.
184*
185 IF( lsame( diag, 'U' ) ) THEN
186 DO 10 j = 1, n
187 ainv( j, j ) = one
188 10 CONTINUE
189 END IF
190*
191* Compute A * AINV, overwriting AINV.
192*
193 IF( lsame( uplo, 'U' ) ) THEN
194 DO 20 j = 1, n
195 CALL ctrmv( 'Upper', 'No transpose', diag, j, a, lda,
196 $ ainv( 1, j ), 1 )
197 20 CONTINUE
198 ELSE
199 DO 30 j = 1, n
200 CALL ctrmv( 'Lower', 'No transpose', diag, n-j+1, a( j, j ),
201 $ lda, ainv( j, j ), 1 )
202 30 CONTINUE
203 END IF
204*
205* Subtract 1 from each diagonal element to form A*AINV - I.
206*
207 DO 40 j = 1, n
208 ainv( j, j ) = ainv( j, j ) - one
209 40 CONTINUE
210*
211* Compute norm(A*AINV - I) / (N * norm(A) * norm(AINV) * EPS)
212*
213 resid = clantr( '1', uplo, 'Non-unit', n, n, ainv, ldainv, rwork )
214*
215 resid = ( ( resid*rcond ) / real( n ) ) / eps
216*
217 RETURN
218*
219* End of CTRT01
220*
real function slamch(cmach)
SLAMCH
Definition slamch.f:68
real function clantr(norm, uplo, diag, m, n, a, lda, work)
CLANTR returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition clantr.f:142
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ctrmv(uplo, trans, diag, n, a, lda, x, incx)
CTRMV
Definition ctrmv.f:147
Here is the call graph for this function:
Here is the caller graph for this function: