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