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