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

◆ strt01()

subroutine strt01 ( character uplo,
character diag,
integer n,
real, dimension( lda, * ) a,
integer lda,
real, dimension( ldainv, * ) ainv,
integer ldainv,
real rcond,
real, dimension( * ) work,
real resid )

STRT01

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