LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zla_gercond_c.f
Go to the documentation of this file.
1 *> \brief \b ZLA_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 ZLA_GERCOND_C + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zla_gercond_c.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zla_gercond_c.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zla_gercond_c.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * DOUBLE PRECISION FUNCTION ZLA_GERCOND_C( TRANS, N, A, LDA, AF,
22 * LDAF, IPIV, C, CAPPLY,
23 * INFO, WORK, RWORK )
24 *
25 * .. Scalar Aguments ..
26 * CHARACTER TRANS
27 * LOGICAL CAPPLY
28 * INTEGER N, LDA, LDAF, INFO
29 * ..
30 * .. Array Arguments ..
31 * INTEGER IPIV( * )
32 * COMPLEX*16 A( LDA, * ), AF( LDAF, * ), WORK( * )
33 * DOUBLE PRECISION C( * ), RWORK( * )
34 * ..
35 *
36 *
37 *> \par Purpose:
38 * =============
39 *>
40 *> \verbatim
41 *>
42 *> ZLA_GERCOND_C computes the infinity norm condition number of
43 *> op(A) * inv(diag(C)) where C is a DOUBLE PRECISION 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*16 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*16 array, dimension (LDAF,N)
80 *> The factors L and U from the factorization
81 *> A = P*L*U as computed by ZGETRF.
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 ZGETRF; row i of the matrix was interchanged
95 *> with row IPIV(i).
96 *> \endverbatim
97 *>
98 *> \param[in] C
99 *> \verbatim
100 *> C is DOUBLE PRECISION 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*16 array, dimension (2*N).
120 *> Workspace.
121 *> \endverbatim
122 *>
123 *> \param[in] RWORK
124 *> \verbatim
125 *> RWORK is DOUBLE PRECISION 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 complex16GEcomputational
140 *
141 * =====================================================================
142  DOUBLE PRECISION FUNCTION zla_gercond_c( TRANS, N, A, LDA, AF,
143  $ ldaf, ipiv, c, capply,
144  $ info, work, rwork )
145 *
146 * -- LAPACK computational routine (version 3.4.2) --
147 * -- LAPACK is a software package provided by Univ. of Tennessee, --
148 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149 * September 2012
150 *
151 * .. Scalar Aguments ..
152  CHARACTER TRANS
153  LOGICAL CAPPLY
154  INTEGER N, LDA, LDAF, INFO
155 * ..
156 * .. Array Arguments ..
157  INTEGER IPIV( * )
158  COMPLEX*16 A( lda, * ), AF( ldaf, * ), WORK( * )
159  DOUBLE PRECISION C( * ), RWORK( * )
160 * ..
161 *
162 * =====================================================================
163 *
164 * .. Local Scalars ..
165  LOGICAL NOTRANS
166  INTEGER KASE, I, J
167  DOUBLE PRECISION AINVNM, ANORM, TMP
168  COMPLEX*16 ZDUM
169 * ..
170 * .. Local Arrays ..
171  INTEGER ISAVE( 3 )
172 * ..
173 * .. External Functions ..
174  LOGICAL LSAME
175  EXTERNAL lsame
176 * ..
177 * .. External Subroutines ..
178  EXTERNAL zlacn2, zgetrs, xerbla
179 * ..
180 * .. Intrinsic Functions ..
181  INTRINSIC abs, max, REAL, DIMAG
182 * ..
183 * .. Statement Functions ..
184  DOUBLE PRECISION CABS1
185 * ..
186 * .. Statement Function Definitions ..
187  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
188 * ..
189 * .. Executable Statements ..
190  zla_gercond_c = 0.0d+0
191 *
192  info = 0
193  notrans = lsame( trans, 'N' )
194  IF ( .NOT. notrans .AND. .NOT. lsame( trans, 'T' ) .AND. .NOT.
195  $ lsame( trans, 'C' ) ) THEN
196  info = -1
197  ELSE IF( n.LT.0 ) THEN
198  info = -2
199  ELSE IF( lda.LT.max( 1, n ) ) THEN
200  info = -4
201  ELSE IF( ldaf.LT.max( 1, n ) ) THEN
202  info = -6
203  END IF
204  IF( info.NE.0 ) THEN
205  CALL xerbla( 'ZLA_GERCOND_C', -info )
206  RETURN
207  END IF
208 *
209 * Compute norm of op(A)*op2(C).
210 *
211  anorm = 0.0d+0
212  IF ( notrans ) THEN
213  DO i = 1, n
214  tmp = 0.0d+0
215  IF ( capply ) THEN
216  DO j = 1, n
217  tmp = tmp + cabs1( a( i, j ) ) / c( j )
218  END DO
219  ELSE
220  DO j = 1, n
221  tmp = tmp + cabs1( a( i, j ) )
222  END DO
223  END IF
224  rwork( i ) = tmp
225  anorm = max( anorm, tmp )
226  END DO
227  ELSE
228  DO i = 1, n
229  tmp = 0.0d+0
230  IF ( capply ) THEN
231  DO j = 1, n
232  tmp = tmp + cabs1( a( j, i ) ) / c( j )
233  END DO
234  ELSE
235  DO j = 1, n
236  tmp = tmp + cabs1( a( j, i ) )
237  END DO
238  END IF
239  rwork( i ) = tmp
240  anorm = max( anorm, tmp )
241  END DO
242  END IF
243 *
244 * Quick return if possible.
245 *
246  IF( n.EQ.0 ) THEN
247  zla_gercond_c = 1.0d+0
248  RETURN
249  ELSE IF( anorm .EQ. 0.0d+0 ) THEN
250  RETURN
251  END IF
252 *
253 * Estimate the norm of inv(op(A)).
254 *
255  ainvnm = 0.0d+0
256 *
257  kase = 0
258  10 CONTINUE
259  CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
260  IF( kase.NE.0 ) THEN
261  IF( kase.EQ.2 ) THEN
262 *
263 * Multiply by R.
264 *
265  DO i = 1, n
266  work( i ) = work( i ) * rwork( i )
267  END DO
268 *
269  IF (notrans) THEN
270  CALL zgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
271  $ work, n, info )
272  ELSE
273  CALL zgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
274  $ work, n, info )
275  ENDIF
276 *
277 * Multiply by inv(C).
278 *
279  IF ( capply ) THEN
280  DO i = 1, n
281  work( i ) = work( i ) * c( i )
282  END DO
283  END IF
284  ELSE
285 *
286 * Multiply by inv(C**H).
287 *
288  IF ( capply ) THEN
289  DO i = 1, n
290  work( i ) = work( i ) * c( i )
291  END DO
292  END IF
293 *
294  IF ( notrans ) THEN
295  CALL zgetrs( 'Conjugate transpose', n, 1, af, ldaf, ipiv,
296  $ work, n, info )
297  ELSE
298  CALL zgetrs( 'No transpose', n, 1, af, ldaf, ipiv,
299  $ work, n, info )
300  END IF
301 *
302 * Multiply by R.
303 *
304  DO i = 1, n
305  work( i ) = work( i ) * rwork( i )
306  END DO
307  END IF
308  GO TO 10
309  END IF
310 *
311 * Compute the estimate of the reciprocal condition number.
312 *
313  IF( ainvnm .NE. 0.0d+0 )
314  $ zla_gercond_c = 1.0d+0 / ainvnm
315 *
316  RETURN
317 *
318  END
subroutine zgetrs(TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZGETRS
Definition: zgetrs.f:123
double precision function zla_gercond_c(TRANS, N, A, LDA, AF, LDAF, IPIV, C, CAPPLY, INFO, WORK, RWORK)
ZLA_GERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for general matrices...
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zlacn2(N, V, X, EST, KASE, ISAVE)
ZLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: zlacn2.f:135