LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dtrt01.f
Go to the documentation of this file.
1*> \brief \b DTRT01
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE DTRT01( UPLO, DIAG, N, A, LDA, AINV, LDAINV, RCOND,
12* WORK, RESID )
13*
14* .. Scalar Arguments ..
15* CHARACTER DIAG, UPLO
16* INTEGER LDA, LDAINV, N
17* DOUBLE PRECISION RCOND, RESID
18* ..
19* .. Array Arguments ..
20* DOUBLE PRECISION A( LDA, * ), AINV( LDAINV, * ), WORK( * )
21* ..
22*
23*
24*> \par Purpose:
25* =============
26*>
27*> \verbatim
28*>
29*> DTRT01 computes the residual for a triangular matrix A times its
30*> inverse:
31*> RESID = norm( A*AINV - I ) / ( N * norm(A) * norm(AINV) * EPS ),
32*> where EPS is the machine epsilon.
33*> \endverbatim
34*
35* Arguments:
36* ==========
37*
38*> \param[in] UPLO
39*> \verbatim
40*> UPLO is CHARACTER*1
41*> Specifies whether the matrix A is upper or lower triangular.
42*> = 'U': Upper triangular
43*> = 'L': Lower triangular
44*> \endverbatim
45*>
46*> \param[in] DIAG
47*> \verbatim
48*> DIAG is CHARACTER*1
49*> Specifies whether or not the matrix A is unit triangular.
50*> = 'N': Non-unit triangular
51*> = 'U': Unit triangular
52*> \endverbatim
53*>
54*> \param[in] N
55*> \verbatim
56*> N is INTEGER
57*> The order of the matrix A. N >= 0.
58*> \endverbatim
59*>
60*> \param[in] A
61*> \verbatim
62*> A is DOUBLE PRECISION array, dimension (LDA,N)
63*> The triangular matrix A. If UPLO = 'U', the leading n by n
64*> upper triangular part of the array A contains the upper
65*> triangular matrix, and the strictly lower triangular part of
66*> A is not referenced. If UPLO = 'L', the leading n by n lower
67*> triangular part of the array A contains the lower triangular
68*> matrix, and the strictly upper triangular part of A is not
69*> referenced. If DIAG = 'U', the diagonal elements of A are
70*> also not referenced and are assumed to be 1.
71*> \endverbatim
72*>
73*> \param[in] LDA
74*> \verbatim
75*> LDA is INTEGER
76*> The leading dimension of the array A. LDA >= max(1,N).
77*> \endverbatim
78*>
79*> \param[in,out] AINV
80*> \verbatim
81*> AINV is DOUBLE PRECISION array, dimension (LDAINV,N)
82*> On entry, the (triangular) inverse of the matrix A, in the
83*> same storage format as A.
84*> On exit, the contents of AINV are destroyed.
85*> \endverbatim
86*>
87*> \param[in] LDAINV
88*> \verbatim
89*> LDAINV is INTEGER
90*> The leading dimension of the array AINV. LDAINV >= max(1,N).
91*> \endverbatim
92*>
93*> \param[out] RCOND
94*> \verbatim
95*> RCOND is DOUBLE PRECISION
96*> The reciprocal condition number of A, computed as
97*> 1/(norm(A) * norm(AINV)).
98*> \endverbatim
99*>
100*> \param[out] WORK
101*> \verbatim
102*> WORK is DOUBLE PRECISION array, dimension (N)
103*> \endverbatim
104*>
105*> \param[out] RESID
106*> \verbatim
107*> RESID is DOUBLE PRECISION
108*> norm(A*AINV - I) / ( N * norm(A) * norm(AINV) * EPS )
109*> \endverbatim
110*
111* Authors:
112* ========
113*
114*> \author Univ. of Tennessee
115*> \author Univ. of California Berkeley
116*> \author Univ. of Colorado Denver
117*> \author NAG Ltd.
118*
119*> \ingroup double_lin
120*
121* =====================================================================
122 SUBROUTINE dtrt01( UPLO, DIAG, N, A, LDA, AINV, LDAINV, RCOND,
123 $ WORK, RESID )
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 DOUBLE PRECISION RCOND, RESID
133* ..
134* .. Array Arguments ..
135 DOUBLE PRECISION A( LDA, * ), AINV( LDAINV, * ), WORK( * )
136* ..
137*
138* =====================================================================
139*
140* .. Parameters ..
141 DOUBLE PRECISION ZERO, ONE
142 parameter( zero = 0.0d+0, one = 1.0d+0 )
143* ..
144* .. Local Scalars ..
145 INTEGER J
146 DOUBLE PRECISION AINVNM, ANORM, EPS
147* ..
148* .. External Functions ..
149 LOGICAL LSAME
150 DOUBLE PRECISION DLAMCH, DLANTR
151 EXTERNAL lsame, dlamch, dlantr
152* ..
153* .. External Subroutines ..
154 EXTERNAL dtrmv
155* ..
156* .. Intrinsic Functions ..
157 INTRINSIC dble
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 = dlamch( 'Epsilon' )
172 anorm = dlantr( '1', uplo, diag, n, n, a, lda, work )
173 ainvnm = dlantr( '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 dtrmv( '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 dtrmv( '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 = dlantr( '1', uplo, 'Non-unit', n, n, ainv, ldainv, work )
212*
213 resid = ( ( resid*rcond ) / dble( n ) ) / eps
214*
215 RETURN
216*
217* End of DTRT01
218*
219 END
subroutine dtrt01(uplo, diag, n, a, lda, ainv, ldainv, rcond, work, resid)
DTRT01
Definition dtrt01.f:124
subroutine dtrmv(uplo, trans, diag, n, a, lda, x, incx)
DTRMV
Definition dtrmv.f:147