LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zget03.f
Go to the documentation of this file.
1*> \brief \b ZGET03
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 ZGET03( N, A, LDA, AINV, LDAINV, WORK, LDWORK, RWORK,
12* RCOND, RESID )
13*
14* .. Scalar Arguments ..
15* INTEGER LDA, LDAINV, LDWORK, N
16* DOUBLE PRECISION RCOND, RESID
17* ..
18* .. Array Arguments ..
19* DOUBLE PRECISION RWORK( * )
20* COMPLEX*16 A( LDA, * ), AINV( LDAINV, * ),
21* $ WORK( LDWORK, * )
22* ..
23*
24*
25*> \par Purpose:
26* =============
27*>
28*> \verbatim
29*>
30*> ZGET03 computes the residual for a general matrix times its inverse:
31*> norm( I - AINV*A ) / ( N * norm(A) * norm(AINV) * EPS ),
32*> where EPS is the machine epsilon.
33*> \endverbatim
34*
35* Arguments:
36* ==========
37*
38*> \param[in] N
39*> \verbatim
40*> N is INTEGER
41*> The number of rows and columns of the matrix A. N >= 0.
42*> \endverbatim
43*>
44*> \param[in] A
45*> \verbatim
46*> A is COMPLEX*16 array, dimension (LDA,N)
47*> The original N x N matrix A.
48*> \endverbatim
49*>
50*> \param[in] LDA
51*> \verbatim
52*> LDA is INTEGER
53*> The leading dimension of the array A. LDA >= max(1,N).
54*> \endverbatim
55*>
56*> \param[in] AINV
57*> \verbatim
58*> AINV is COMPLEX*16 array, dimension (LDAINV,N)
59*> The inverse of the matrix A.
60*> \endverbatim
61*>
62*> \param[in] LDAINV
63*> \verbatim
64*> LDAINV is INTEGER
65*> The leading dimension of the array AINV. LDAINV >= max(1,N).
66*> \endverbatim
67*>
68*> \param[out] WORK
69*> \verbatim
70*> WORK is COMPLEX*16 array, dimension (LDWORK,N)
71*> \endverbatim
72*>
73*> \param[in] LDWORK
74*> \verbatim
75*> LDWORK is INTEGER
76*> The leading dimension of the array WORK. LDWORK >= max(1,N).
77*> \endverbatim
78*>
79*> \param[out] RWORK
80*> \verbatim
81*> RWORK is DOUBLE PRECISION array, dimension (N)
82*> \endverbatim
83*>
84*> \param[out] RCOND
85*> \verbatim
86*> RCOND is DOUBLE PRECISION
87*> The reciprocal of the condition number of A, computed as
88*> ( 1/norm(A) ) / norm(AINV).
89*> \endverbatim
90*>
91*> \param[out] RESID
92*> \verbatim
93*> RESID is DOUBLE PRECISION
94*> norm(I - AINV*A) / ( N * norm(A) * norm(AINV) * EPS )
95*> \endverbatim
96*
97* Authors:
98* ========
99*
100*> \author Univ. of Tennessee
101*> \author Univ. of California Berkeley
102*> \author Univ. of Colorado Denver
103*> \author NAG Ltd.
104*
105*> \ingroup complex16_lin
106*
107* =====================================================================
108 SUBROUTINE zget03( N, A, LDA, AINV, LDAINV, WORK, LDWORK, RWORK,
109 $ RCOND, RESID )
110*
111* -- LAPACK test routine --
112* -- LAPACK is a software package provided by Univ. of Tennessee, --
113* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114*
115* .. Scalar Arguments ..
116 INTEGER LDA, LDAINV, LDWORK, N
117 DOUBLE PRECISION RCOND, RESID
118* ..
119* .. Array Arguments ..
120 DOUBLE PRECISION RWORK( * )
121 COMPLEX*16 A( LDA, * ), AINV( LDAINV, * ),
122 $ work( ldwork, * )
123* ..
124*
125* =====================================================================
126*
127* .. Parameters ..
128 DOUBLE PRECISION ZERO, ONE
129 parameter( zero = 0.0d+0, one = 1.0d+0 )
130 COMPLEX*16 CZERO, CONE
131 parameter( czero = ( 0.0d+0, 0.0d+0 ),
132 $ cone = ( 1.0d+0, 0.0d+0 ) )
133* ..
134* .. Local Scalars ..
135 INTEGER I
136 DOUBLE PRECISION AINVNM, ANORM, EPS
137* ..
138* .. External Functions ..
139 DOUBLE PRECISION DLAMCH, ZLANGE
140 EXTERNAL dlamch, zlange
141* ..
142* .. External Subroutines ..
143 EXTERNAL zgemm
144* ..
145* .. Intrinsic Functions ..
146 INTRINSIC dble
147* ..
148* .. Executable Statements ..
149*
150* Quick exit if N = 0.
151*
152 IF( n.LE.0 ) THEN
153 rcond = one
154 resid = zero
155 RETURN
156 END IF
157*
158* Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
159*
160 eps = dlamch( 'Epsilon' )
161 anorm = zlange( '1', n, n, a, lda, rwork )
162 ainvnm = zlange( '1', n, n, ainv, ldainv, rwork )
163 IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
164 rcond = zero
165 resid = one / eps
166 RETURN
167 END IF
168 rcond = ( one / anorm ) / ainvnm
169*
170* Compute I - A * AINV
171*
172 CALL zgemm( 'No transpose', 'No transpose', n, n, n, -cone, ainv,
173 $ ldainv, a, lda, czero, work, ldwork )
174 DO 10 i = 1, n
175 work( i, i ) = cone + work( i, i )
176 10 CONTINUE
177*
178* Compute norm(I - AINV*A) / (N * norm(A) * norm(AINV) * EPS)
179*
180 resid = zlange( '1', n, n, work, ldwork, rwork )
181*
182 resid = ( ( resid*rcond ) / eps ) / dble( n )
183*
184 RETURN
185*
186* End of ZGET03
187*
188 END
subroutine zgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
ZGEMM
Definition zgemm.f:188
subroutine zget03(n, a, lda, ainv, ldainv, work, ldwork, rwork, rcond, resid)
ZGET03
Definition zget03.f:110