LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cla_gercond_c.f
Go to the documentation of this file.
1*> \brief \b CLA_GERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for general matrices.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CLA_GERCOND_C + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cla_gercond_c.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cla_gercond_c.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cla_gercond_c.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* REAL FUNCTION CLA_GERCOND_C( TRANS, N, A, LDA, AF, LDAF, IPIV, C,
22* CAPPLY, INFO, WORK, RWORK )
23*
24* .. Scalar Arguments ..
25* CHARACTER TRANS
26* LOGICAL CAPPLY
27* INTEGER N, LDA, LDAF, INFO
28* ..
29* .. Array Arguments ..
30* INTEGER IPIV( * )
31* COMPLEX A( LDA, * ), AF( LDAF, * ), WORK( * )
32* REAL C( * ), RWORK( * )
33* ..
34*
35*
36*> \par Purpose:
37* =============
38*>
39*> \verbatim
40*>
41*>
42*> CLA_GERCOND_C computes the infinity norm condition number of
43*> op(A) * inv(diag(C)) where C is a REAL vector.
44*> \endverbatim
45*
46* Arguments:
47* ==========
48*
49*> \param[in] TRANS
50*> \verbatim
51*> TRANS is CHARACTER*1
52*> Specifies the form of the system of equations:
53*> = 'N': A * X = B (No transpose)
54*> = 'T': A**T * X = B (Transpose)
55*> = 'C': A**H * X = B (Conjugate Transpose = Transpose)
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*> N is INTEGER
61*> The number of linear equations, i.e., the order of the
62*> matrix A. N >= 0.
63*> \endverbatim
64*>
65*> \param[in] A
66*> \verbatim
67*> A is COMPLEX array, dimension (LDA,N)
68*> On entry, the N-by-N matrix A
69*> \endverbatim
70*>
71*> \param[in] LDA
72*> \verbatim
73*> LDA is INTEGER
74*> The leading dimension of the array A. LDA >= max(1,N).
75*> \endverbatim
76*>
77*> \param[in] AF
78*> \verbatim
79*> AF is COMPLEX array, dimension (LDAF,N)
80*> The factors L and U from the factorization
81*> A = P*L*U as computed by CGETRF.
82*> \endverbatim
83*>
84*> \param[in] LDAF
85*> \verbatim
86*> LDAF is INTEGER
87*> The leading dimension of the array AF. LDAF >= max(1,N).
88*> \endverbatim
89*>
90*> \param[in] IPIV
91*> \verbatim
92*> IPIV is INTEGER array, dimension (N)
93*> The pivot indices from the factorization A = P*L*U
94*> as computed by CGETRF; row i of the matrix was interchanged
95*> with row IPIV(i).
96*> \endverbatim
97*>
98*> \param[in] C
99*> \verbatim
100*> C is REAL array, dimension (N)
101*> The vector C in the formula op(A) * inv(diag(C)).
102*> \endverbatim
103*>
104*> \param[in] CAPPLY
105*> \verbatim
106*> CAPPLY is LOGICAL
107*> If .TRUE. then access the vector C in the formula above.
108*> \endverbatim
109*>
110*> \param[out] INFO
111*> \verbatim
112*> INFO is INTEGER
113*> = 0: Successful exit.
114*> i > 0: The ith argument is invalid.
115*> \endverbatim
116*>
117*> \param[out] WORK
118*> \verbatim
119*> WORK is COMPLEX array, dimension (2*N).
120*> Workspace.
121*> \endverbatim
122*>
123*> \param[out] RWORK
124*> \verbatim
125*> RWORK is REAL array, dimension (N).
126*> Workspace.
127*> \endverbatim
128*
129* Authors:
130* ========
131*
132*> \author Univ. of Tennessee
133*> \author Univ. of California Berkeley
134*> \author Univ. of Colorado Denver
135*> \author NAG Ltd.
136*
137*> \ingroup la_gercond
138*
139* =====================================================================
140 REAL function cla_gercond_c( trans, n, a, lda, af, ldaf, ipiv, c,
141 $ capply, info, work, rwork )
142*
143* -- LAPACK computational routine --
144* -- LAPACK is a software package provided by Univ. of Tennessee, --
145* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146*
147* .. Scalar Arguments ..
148 CHARACTER trans
149 LOGICAL capply
150 INTEGER n, lda, ldaf, info
151* ..
152* .. Array Arguments ..
153 INTEGER ipiv( * )
154 COMPLEX a( lda, * ), af( ldaf, * ), work( * )
155 REAL c( * ), rwork( * )
156* ..
157*
158* =====================================================================
159*
160* .. Local Scalars ..
161 LOGICAL notrans
162 INTEGER kase, i, j
163 REAL ainvnm, anorm, tmp
164 COMPLEX zdum
165* ..
166* .. Local Arrays ..
167 INTEGER isave( 3 )
168* ..
169* .. External Functions ..
170 LOGICAL lsame
171 EXTERNAL lsame
172* ..
173* .. External Subroutines ..
174 EXTERNAL clacn2, cgetrs, xerbla
175* ..
176* .. Intrinsic Functions ..
177 INTRINSIC abs, max, real, aimag
178* ..
179* .. Statement Functions ..
180 REAL cabs1
181* ..
182* .. Statement Function Definitions ..
183 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
184* ..
185* .. Executable Statements ..
186 cla_gercond_c = 0.0e+0
187*
188 info = 0
189 notrans = lsame( trans, 'N' )
190 IF ( .NOT. notrans .AND. .NOT. lsame( trans, 'T' ) .AND. .NOT.
191 $ lsame( trans, 'C' ) ) THEN
192 info = -1
193 ELSE IF( n.LT.0 ) THEN
194 info = -2
195 ELSE IF( lda.LT.max( 1, n ) ) THEN
196 info = -4
197 ELSE IF( ldaf.LT.max( 1, n ) ) THEN
198 info = -6
199 END IF
200 IF( info.NE.0 ) THEN
201 CALL xerbla( 'CLA_GERCOND_C', -info )
202 RETURN
203 END IF
204*
205* Compute norm of op(A)*op2(C).
206*
207 anorm = 0.0e+0
208 IF ( notrans ) THEN
209 DO i = 1, n
210 tmp = 0.0e+0
211 IF ( capply ) THEN
212 DO j = 1, n
213 tmp = tmp + cabs1( a( i, j ) ) / c( j )
214 END DO
215 ELSE
216 DO j = 1, n
217 tmp = tmp + cabs1( a( i, j ) )
218 END DO
219 END IF
220 rwork( i ) = tmp
221 anorm = max( anorm, tmp )
222 END DO
223 ELSE
224 DO i = 1, n
225 tmp = 0.0e+0
226 IF ( capply ) THEN
227 DO j = 1, n
228 tmp = tmp + cabs1( a( j, i ) ) / c( j )
229 END DO
230 ELSE
231 DO j = 1, n
232 tmp = tmp + cabs1( a( j, i ) )
233 END DO
234 END IF
235 rwork( i ) = tmp
236 anorm = max( anorm, tmp )
237 END DO
238 END IF
239*
240* Quick return if possible.
241*
242 IF( n.EQ.0 ) THEN
243 cla_gercond_c = 1.0e+0
244 RETURN
245 ELSE IF( anorm .EQ. 0.0e+0 ) THEN
246 RETURN
247 END IF
248*
249* Estimate the norm of inv(op(A)).
250*
251 ainvnm = 0.0e+0
252*
253 kase = 0
254 10 CONTINUE
255 CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
256 IF( kase.NE.0 ) THEN
257 IF( kase.EQ.2 ) THEN
258*
259* Multiply by R.
260*
261 DO i = 1, n
262 work( i ) = work( i ) * rwork( i )
263 END DO
264*
265 IF (notrans) THEN
266 CALL cgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
267 $ work, n, info )
268 ELSE
269 CALL cgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
270 $ work, n, info )
271 ENDIF
272*
273* Multiply by inv(C).
274*
275 IF ( capply ) THEN
276 DO i = 1, n
277 work( i ) = work( i ) * c( i )
278 END DO
279 END IF
280 ELSE
281*
282* Multiply by inv(C**H).
283*
284 IF ( capply ) THEN
285 DO i = 1, n
286 work( i ) = work( i ) * c( i )
287 END DO
288 END IF
289*
290 IF ( notrans ) THEN
291 CALL cgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
292 $ work, n, info )
293 ELSE
294 CALL cgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
295 $ work, n, info )
296 END IF
297*
298* Multiply by R.
299*
300 DO i = 1, n
301 work( i ) = work( i ) * rwork( i )
302 END DO
303 END IF
304 GO TO 10
305 END IF
306*
307* Compute the estimate of the reciprocal condition number.
308*
309 IF( ainvnm .NE. 0.0e+0 )
310 $ cla_gercond_c = 1.0e+0 / ainvnm
311*
312 RETURN
313*
314* End of CLA_GERCOND_C
315*
316 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
CGETRS
Definition cgetrs.f:121
real function cla_gercond_c(trans, n, a, lda, af, ldaf, ipiv, c, capply, info, work, rwork)
CLA_GERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for general matrices.
subroutine clacn2(n, v, x, est, kase, isave)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition clacn2.f:133
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48