LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2011

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