LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cla_hercond_c.f
Go to the documentation of this file.
1 *> \brief \b CLA_HERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for Hermitian indefinite 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_HERCOND_C + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cla_hercond_c.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cla_hercond_c.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cla_hercond_c.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * REAL FUNCTION CLA_HERCOND_C( UPLO, N, A, LDA, AF, LDAF, IPIV, C,
22 * CAPPLY, INFO, WORK, RWORK )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER UPLO
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 *> CLA_HERCOND_C computes the infinity norm condition number of
42 *> op(A) * inv(diag(C)) where C is a REAL vector.
43 *> \endverbatim
44 *
45 * Arguments:
46 * ==========
47 *
48 *> \param[in] UPLO
49 *> \verbatim
50 *> UPLO is CHARACTER*1
51 *> = 'U': Upper triangle of A is stored;
52 *> = 'L': Lower triangle of A is stored.
53 *> \endverbatim
54 *>
55 *> \param[in] N
56 *> \verbatim
57 *> N is INTEGER
58 *> The number of linear equations, i.e., the order of the
59 *> matrix A. N >= 0.
60 *> \endverbatim
61 *>
62 *> \param[in] A
63 *> \verbatim
64 *> A is COMPLEX array, dimension (LDA,N)
65 *> On entry, the N-by-N matrix A
66 *> \endverbatim
67 *>
68 *> \param[in] LDA
69 *> \verbatim
70 *> LDA is INTEGER
71 *> The leading dimension of the array A. LDA >= max(1,N).
72 *> \endverbatim
73 *>
74 *> \param[in] AF
75 *> \verbatim
76 *> AF is COMPLEX array, dimension (LDAF,N)
77 *> The block diagonal matrix D and the multipliers used to
78 *> obtain the factor U or L as computed by CHETRF.
79 *> \endverbatim
80 *>
81 *> \param[in] LDAF
82 *> \verbatim
83 *> LDAF is INTEGER
84 *> The leading dimension of the array AF. LDAF >= max(1,N).
85 *> \endverbatim
86 *>
87 *> \param[in] IPIV
88 *> \verbatim
89 *> IPIV is INTEGER array, dimension (N)
90 *> Details of the interchanges and the block structure of D
91 *> as determined by CHETRF.
92 *> \endverbatim
93 *>
94 *> \param[in] C
95 *> \verbatim
96 *> C is REAL array, dimension (N)
97 *> The vector C in the formula op(A) * inv(diag(C)).
98 *> \endverbatim
99 *>
100 *> \param[in] CAPPLY
101 *> \verbatim
102 *> CAPPLY is LOGICAL
103 *> If .TRUE. then access the vector C in the formula above.
104 *> \endverbatim
105 *>
106 *> \param[out] INFO
107 *> \verbatim
108 *> INFO is INTEGER
109 *> = 0: Successful exit.
110 *> i > 0: The ith argument is invalid.
111 *> \endverbatim
112 *>
113 *> \param[in] WORK
114 *> \verbatim
115 *> WORK is COMPLEX array, dimension (2*N).
116 *> Workspace.
117 *> \endverbatim
118 *>
119 *> \param[in] RWORK
120 *> \verbatim
121 *> RWORK is REAL array, dimension (N).
122 *> Workspace.
123 *> \endverbatim
124 *
125 * Authors:
126 * ========
127 *
128 *> \author Univ. of Tennessee
129 *> \author Univ. of California Berkeley
130 *> \author Univ. of Colorado Denver
131 *> \author NAG Ltd.
132 *
133 *> \date September 2012
134 *
135 *> \ingroup complexHEcomputational
136 *
137 * =====================================================================
138  REAL FUNCTION cla_hercond_c( UPLO, N, A, LDA, AF, LDAF, IPIV, C,
139  $ capply, info, work, rwork )
140 *
141 * -- LAPACK computational routine (version 3.4.2) --
142 * -- LAPACK is a software package provided by Univ. of Tennessee, --
143 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
144 * September 2012
145 *
146 * .. Scalar Arguments ..
147  CHARACTER UPLO
148  LOGICAL CAPPLY
149  INTEGER N, LDA, LDAF, INFO
150 * ..
151 * .. Array Arguments ..
152  INTEGER IPIV( * )
153  COMPLEX A( lda, * ), AF( ldaf, * ), WORK( * )
154  REAL C ( * ), RWORK( * )
155 * ..
156 *
157 * =====================================================================
158 *
159 * .. Local Scalars ..
160  INTEGER KASE, I, J
161  REAL AINVNM, ANORM, TMP
162  LOGICAL UP, UPPER
163  COMPLEX ZDUM
164 * ..
165 * .. Local Arrays ..
166  INTEGER ISAVE( 3 )
167 * ..
168 * .. External Functions ..
169  LOGICAL LSAME
170  EXTERNAL lsame
171 * ..
172 * .. External Subroutines ..
173  EXTERNAL clacn2, chetrs, xerbla
174 * ..
175 * .. Intrinsic Functions ..
176  INTRINSIC abs, max
177 * ..
178 * .. Statement Functions ..
179  REAL CABS1
180 * ..
181 * .. Statement Function Definitions ..
182  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( AIMAG( zdum ) )
183 * ..
184 * .. Executable Statements ..
185 *
186  cla_hercond_c = 0.0e+0
187 *
188  info = 0
189  upper = lsame( uplo, 'U' )
190  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
191  info = -1
192  ELSE IF( n.LT.0 ) THEN
193  info = -2
194  ELSE IF( lda.LT.max( 1, n ) ) THEN
195  info = -4
196  ELSE IF( ldaf.LT.max( 1, n ) ) THEN
197  info = -6
198  END IF
199  IF( info.NE.0 ) THEN
200  CALL xerbla( 'CLA_HERCOND_C', -info )
201  RETURN
202  END IF
203  up = .false.
204  IF ( lsame( uplo, 'U' ) ) up = .true.
205 *
206 * Compute norm of op(A)*op2(C).
207 *
208  anorm = 0.0e+0
209  IF ( up ) THEN
210  DO i = 1, n
211  tmp = 0.0e+0
212  IF ( capply ) THEN
213  DO j = 1, i
214  tmp = tmp + cabs1( a( j, i ) ) / c( j )
215  END DO
216  DO j = i+1, n
217  tmp = tmp + cabs1( a( i, j ) ) / c( j )
218  END DO
219  ELSE
220  DO j = 1, i
221  tmp = tmp + cabs1( a( j, i ) )
222  END DO
223  DO j = i+1, n
224  tmp = tmp + cabs1( a( i, j ) )
225  END DO
226  END IF
227  rwork( i ) = tmp
228  anorm = max( anorm, tmp )
229  END DO
230  ELSE
231  DO i = 1, n
232  tmp = 0.0e+0
233  IF ( capply ) THEN
234  DO j = 1, i
235  tmp = tmp + cabs1( a( i, j ) ) / c( j )
236  END DO
237  DO j = i+1, n
238  tmp = tmp + cabs1( a( j, i ) ) / c( j )
239  END DO
240  ELSE
241  DO j = 1, i
242  tmp = tmp + cabs1( a( i, j ) )
243  END DO
244  DO j = i+1, n
245  tmp = tmp + cabs1( a( j, i ) )
246  END DO
247  END IF
248  rwork( i ) = tmp
249  anorm = max( anorm, tmp )
250  END DO
251  END IF
252 *
253 * Quick return if possible.
254 *
255  IF( n.EQ.0 ) THEN
256  cla_hercond_c = 1.0e+0
257  RETURN
258  ELSE IF( anorm .EQ. 0.0e+0 ) THEN
259  RETURN
260  END IF
261 *
262 * Estimate the norm of inv(op(A)).
263 *
264  ainvnm = 0.0e+0
265 *
266  kase = 0
267  10 CONTINUE
268  CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
269  IF( kase.NE.0 ) THEN
270  IF( kase.EQ.2 ) THEN
271 *
272 * Multiply by R.
273 *
274  DO i = 1, n
275  work( i ) = work( i ) * rwork( i )
276  END DO
277 *
278  IF ( up ) THEN
279  CALL chetrs( 'U', n, 1, af, ldaf, ipiv,
280  $ work, n, info )
281  ELSE
282  CALL chetrs( 'L', n, 1, af, ldaf, ipiv,
283  $ work, n, info )
284  ENDIF
285 *
286 * Multiply by inv(C).
287 *
288  IF ( capply ) THEN
289  DO i = 1, n
290  work( i ) = work( i ) * c( i )
291  END DO
292  END IF
293  ELSE
294 *
295 * Multiply by inv(C**H).
296 *
297  IF ( capply ) THEN
298  DO i = 1, n
299  work( i ) = work( i ) * c( i )
300  END DO
301  END IF
302 *
303  IF ( up ) THEN
304  CALL chetrs( 'U', n, 1, af, ldaf, ipiv,
305  $ work, n, info )
306  ELSE
307  CALL chetrs( 'L', n, 1, af, ldaf, ipiv,
308  $ work, n, info )
309  END IF
310 *
311 * Multiply by R.
312 *
313  DO i = 1, n
314  work( i ) = work( i ) * rwork( i )
315  END DO
316  END IF
317  GO TO 10
318  END IF
319 *
320 * Compute the estimate of the reciprocal condition number.
321 *
322  IF( ainvnm .NE. 0.0e+0 )
323  $ cla_hercond_c = 1.0e+0 / ainvnm
324 *
325  RETURN
326 *
327  END
real function cla_hercond_c(UPLO, N, A, LDA, AF, LDAF, IPIV, C, CAPPLY, INFO, WORK, RWORK)
CLA_HERCOND_C computes the infinity norm condition number of op(A)*inv(diag(c)) for Hermitian indefin...
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine chetrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CHETRS
Definition: chetrs.f:122
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