LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 Aguments ..
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[in] WORK
118 *> \verbatim
119 *> WORK is COMPLEX array, dimension (2*N).
120 *> Workspace.
121 *> \endverbatim
122 *>
123 *> \param[in] 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 *> \date September 2012
138 *
139 *> \ingroup complexGEcomputational
140 *
141 * =====================================================================
142  REAL FUNCTION cla_gercond_c( TRANS, N, A, LDA, AF, LDAF, IPIV, C,
143  $ capply, info, work, rwork )
144 *
145 * -- LAPACK computational routine (version 3.4.2) --
146 * -- LAPACK is a software package provided by Univ. of Tennessee, --
147 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148 * September 2012
149 *
150 * .. Scalar Aguments ..
151  CHARACTER TRANS
152  LOGICAL CAPPLY
153  INTEGER N, LDA, LDAF, INFO
154 * ..
155 * .. Array Arguments ..
156  INTEGER IPIV( * )
157  COMPLEX A( lda, * ), AF( ldaf, * ), WORK( * )
158  REAL C( * ), RWORK( * )
159 * ..
160 *
161 * =====================================================================
162 *
163 * .. Local Scalars ..
164  LOGICAL NOTRANS
165  INTEGER KASE, I, J
166  REAL AINVNM, ANORM, TMP
167  COMPLEX ZDUM
168 * ..
169 * .. Local Arrays ..
170  INTEGER ISAVE( 3 )
171 * ..
172 * .. External Functions ..
173  LOGICAL LSAME
174  EXTERNAL lsame
175 * ..
176 * .. External Subroutines ..
177  EXTERNAL clacn2, cgetrs, xerbla
178 * ..
179 * .. Intrinsic Functions ..
180  INTRINSIC abs, max, REAL, AIMAG
181 * ..
182 * .. Statement Functions ..
183  REAL CABS1
184 * ..
185 * .. Statement Function Definitions ..
186  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( AIMAG( zdum ) )
187 * ..
188 * .. Executable Statements ..
189  cla_gercond_c = 0.0e+0
190 *
191  info = 0
192  notrans = lsame( trans, 'N' )
193  IF ( .NOT. notrans .AND. .NOT. lsame( trans, 'T' ) .AND. .NOT.
194  $ lsame( trans, 'C' ) ) THEN
195  info = -1
196  ELSE IF( n.LT.0 ) THEN
197  info = -2
198  ELSE IF( lda.LT.max( 1, n ) ) THEN
199  info = -4
200  ELSE IF( ldaf.LT.max( 1, n ) ) THEN
201  info = -6
202  END IF
203  IF( info.NE.0 ) THEN
204  CALL xerbla( 'CLA_GERCOND_C', -info )
205  RETURN
206  END IF
207 *
208 * Compute norm of op(A)*op2(C).
209 *
210  anorm = 0.0e+0
211  IF ( notrans ) THEN
212  DO i = 1, n
213  tmp = 0.0e+0
214  IF ( capply ) THEN
215  DO j = 1, n
216  tmp = tmp + cabs1( a( i, j ) ) / c( j )
217  END DO
218  ELSE
219  DO j = 1, n
220  tmp = tmp + cabs1( a( i, j ) )
221  END DO
222  END IF
223  rwork( i ) = tmp
224  anorm = max( anorm, tmp )
225  END DO
226  ELSE
227  DO i = 1, n
228  tmp = 0.0e+0
229  IF ( capply ) THEN
230  DO j = 1, n
231  tmp = tmp + cabs1( a( j, i ) ) / c( j )
232  END DO
233  ELSE
234  DO j = 1, n
235  tmp = tmp + cabs1( a( j, i ) )
236  END DO
237  END IF
238  rwork( i ) = tmp
239  anorm = max( anorm, tmp )
240  END DO
241  END IF
242 *
243 * Quick return if possible.
244 *
245  IF( n.EQ.0 ) THEN
246  cla_gercond_c = 1.0e+0
247  RETURN
248  ELSE IF( anorm .EQ. 0.0e+0 ) THEN
249  RETURN
250  END IF
251 *
252 * Estimate the norm of inv(op(A)).
253 *
254  ainvnm = 0.0e+0
255 *
256  kase = 0
257  10 CONTINUE
258  CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
259  IF( kase.NE.0 ) THEN
260  IF( kase.EQ.2 ) THEN
261 *
262 * Multiply by R.
263 *
264  DO i = 1, n
265  work( i ) = work( i ) * rwork( i )
266  END DO
267 *
268  IF (notrans) THEN
269  CALL cgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
270  $ work, n, info )
271  ELSE
272  CALL cgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
273  $ work, n, info )
274  ENDIF
275 *
276 * Multiply by inv(C).
277 *
278  IF ( capply ) THEN
279  DO i = 1, n
280  work( i ) = work( i ) * c( i )
281  END DO
282  END IF
283  ELSE
284 *
285 * Multiply by inv(C**H).
286 *
287  IF ( capply ) THEN
288  DO i = 1, n
289  work( i ) = work( i ) * c( i )
290  END DO
291  END IF
292 *
293  IF ( notrans ) THEN
294  CALL cgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
295  $ work, n, info )
296  ELSE
297  CALL cgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
298  $ work, n, info )
299  END IF
300 *
301 * Multiply by R.
302 *
303  DO i = 1, n
304  work( i ) = work( i ) * rwork( i )
305  END DO
306  END IF
307  GO TO 10
308  END IF
309 *
310 * Compute the estimate of the reciprocal condition number.
311 *
312  IF( ainvnm .NE. 0.0e+0 )
313  $ cla_gercond_c = 1.0e+0 / ainvnm
314 *
315  RETURN
316 *
317  END
subroutine cgetrs(TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CGETRS
Definition: cgetrs.f:123
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:135