OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cgecon.f
Go to the documentation of this file.
1*> \brief \b CGECON
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CGECON + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgecon.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgecon.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgecon.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE CGECON( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
22* INFO )
23*
24* .. Scalar Arguments ..
25* CHARACTER NORM
26* INTEGER INFO, LDA, N
27* REAL ANORM, RCOND
28* ..
29* .. Array Arguments ..
30* REAL RWORK( * )
31* COMPLEX A( LDA, * ), WORK( * )
32* ..
33*
34*
35*> \par Purpose:
36* =============
37*>
38*> \verbatim
39*>
40*> CGECON estimates the reciprocal of the condition number of a general
41*> complex matrix A, in either the 1-norm or the infinity-norm, using
42*> the LU factorization computed by CGETRF.
43*>
44*> An estimate is obtained for norm(inv(A)), and the reciprocal of the
45*> condition number is computed as
46*> RCOND = 1 / ( norm(A) * norm(inv(A)) ).
47*> \endverbatim
48*
49* Arguments:
50* ==========
51*
52*> \param[in] NORM
53*> \verbatim
54*> NORM is CHARACTER*1
55*> Specifies whether the 1-norm condition number or the
56*> infinity-norm condition number is required:
57*> = '1' or 'O': 1-norm;
58*> = 'I': Infinity-norm.
59*> \endverbatim
60*>
61*> \param[in] N
62*> \verbatim
63*> N is INTEGER
64*> The order of the matrix A. N >= 0.
65*> \endverbatim
66*>
67*> \param[in] A
68*> \verbatim
69*> A is COMPLEX array, dimension (LDA,N)
70*> The factors L and U from the factorization A = P*L*U
71*> as computed by CGETRF.
72*> \endverbatim
73*>
74*> \param[in] LDA
75*> \verbatim
76*> LDA is INTEGER
77*> The leading dimension of the array A. LDA >= max(1,N).
78*> \endverbatim
79*>
80*> \param[in] ANORM
81*> \verbatim
82*> ANORM is REAL
83*> If NORM = '1' or 'O', the 1-norm of the original matrix A.
84*> If NORM = 'I', the infinity-norm of the original matrix A.
85*> \endverbatim
86*>
87*> \param[out] RCOND
88*> \verbatim
89*> RCOND is REAL
90*> The reciprocal of the condition number of the matrix A,
91*> computed as RCOND = 1/(norm(A) * norm(inv(A))).
92*> \endverbatim
93*>
94*> \param[out] WORK
95*> \verbatim
96*> WORK is COMPLEX array, dimension (2*N)
97*> \endverbatim
98*>
99*> \param[out] RWORK
100*> \verbatim
101*> RWORK is REAL array, dimension (2*N)
102*> \endverbatim
103*>
104*> \param[out] INFO
105*> \verbatim
106*> INFO is INTEGER
107*> = 0: successful exit
108*> < 0: if INFO = -i, the i-th argument had an illegal value
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 complexGEcomputational
120*
121* =====================================================================
122 SUBROUTINE cgecon( NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK,
123 $ INFO )
124*
125* -- LAPACK computational 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 NORM
131 INTEGER INFO, LDA, N
132 REAL ANORM, RCOND
133* ..
134* .. Array Arguments ..
135 REAL RWORK( * )
136 COMPLEX A( LDA, * ), WORK( * )
137* ..
138*
139* =====================================================================
140*
141* .. Parameters ..
142 REAL ONE, ZERO
143 parameter( one = 1.0e+0, zero = 0.0e+0 )
144* ..
145* .. Local Scalars ..
146 LOGICAL ONENRM
147 CHARACTER NORMIN
148 INTEGER IX, KASE, KASE1
149 REAL AINVNM, SCALE, SL, SMLNUM, SU
150 COMPLEX ZDUM
151* ..
152* .. Local Arrays ..
153 INTEGER ISAVE( 3 )
154* ..
155* .. External Functions ..
156 LOGICAL LSAME
157 INTEGER ICAMAX
158 REAL SLAMCH
159 EXTERNAL lsame, icamax, slamch
160* ..
161* .. External Subroutines ..
162 EXTERNAL clacn2, clatrs, csrscl, xerbla
163* ..
164* .. Intrinsic Functions ..
165 INTRINSIC abs, aimag, max, real
166* ..
167* .. Statement Functions ..
168 REAL CABS1
169* ..
170* .. Statement Function definitions ..
171 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
172* ..
173* .. Executable Statements ..
174*
175* Test the input parameters.
176*
177 info = 0
178 onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
179 IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
180 info = -1
181 ELSE IF( n.LT.0 ) THEN
182 info = -2
183 ELSE IF( lda.LT.max( 1, n ) ) THEN
184 info = -4
185 ELSE IF( anorm.LT.zero ) THEN
186 info = -5
187 END IF
188 IF( info.NE.0 ) THEN
189 CALL xerbla( 'cgecon', -INFO )
190 RETURN
191 END IF
192*
193* Quick return if possible
194*
195 RCOND = ZERO
196.EQ. IF( N0 ) THEN
197 RCOND = ONE
198 RETURN
199.EQ. ELSE IF( ANORMZERO ) THEN
200 RETURN
201 END IF
202*
203 SMLNUM = SLAMCH( 'safe minimum' )
204*
205* Estimate the norm of inv(A).
206*
207 AINVNM = ZERO
208 NORMIN = 'n'
209 IF( ONENRM ) THEN
210 KASE1 = 1
211 ELSE
212 KASE1 = 2
213 END IF
214 KASE = 0
215 10 CONTINUE
216 CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
217.NE. IF( KASE0 ) THEN
218.EQ. IF( KASEKASE1 ) THEN
219*
220* Multiply by inv(L).
221*
222 CALL CLATRS( 'lower', 'no transpose', 'unit', NORMIN, N, A,
223 $ LDA, WORK, SL, RWORK, INFO )
224*
225* Multiply by inv(U).
226*
227 CALL CLATRS( 'upper', 'no transpose', 'non-unit', NORMIN, N,
228 $ A, LDA, WORK, SU, RWORK( N+1 ), INFO )
229 ELSE
230*
231* Multiply by inv(U**H).
232*
233 CALL CLATRS( 'upper', 'conjugate transpose', 'non-unit',
234 $ NORMIN, N, A, LDA, WORK, SU, RWORK( N+1 ),
235 $ INFO )
236*
237* Multiply by inv(L**H).
238*
239 CALL CLATRS( 'lower', 'conjugate transpose', 'unit', NORMIN,
240 $ N, A, LDA, WORK, SL, RWORK, INFO )
241 END IF
242*
243* Divide X by 1/(SL*SU) if doing so will not cause overflow.
244*
245 SCALE = SL*SU
246 NORMIN = 'y'
247.NE. IF( SCALEONE ) THEN
248 IX = ICAMAX( N, WORK, 1 )
249.LT..OR..EQ. IF( SCALECABS1( WORK( IX ) )*SMLNUM SCALEZERO )
250 $ GO TO 20
251 CALL CSRSCL( N, SCALE, WORK, 1 )
252 END IF
253 GO TO 10
254 END IF
255*
256* Compute the estimate of the reciprocal condition number.
257*
258.NE. IF( AINVNMZERO )
259 $ RCOND = ( ONE / AINVNM ) / ANORM
260*
261 20 CONTINUE
262 RETURN
263*
264* End of CGECON
265*
266 END
subroutine xerbla(srname, info)
XERBLA
Definition xerbla.f:60
subroutine cgecon(norm, n, a, lda, anorm, rcond, work, rwork, info)
CGECON
Definition cgecon.f:124
subroutine csrscl(n, sa, sx, incx)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
Definition csrscl.f:84
subroutine clatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
CLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition clatrs.f:239
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
#define max(a, b)
Definition macros.h:21