LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zla_syrcond_x.f
Go to the documentation of this file.
1 *> \brief \b ZLA_SYRCOND_X computes the infinity norm condition number of op(A)*diag(x) 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_X + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zla_syrcond_x.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zla_syrcond_x.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zla_syrcond_x.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * DOUBLE PRECISION FUNCTION ZLA_SYRCOND_X( UPLO, N, A, LDA, AF,
22 * LDAF, IPIV, X, INFO,
23 * WORK, RWORK )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER UPLO
27 * INTEGER N, LDA, LDAF, INFO
28 * ..
29 * .. Array Arguments ..
30 * INTEGER IPIV( * )
31 * COMPLEX*16 A( LDA, * ), AF( LDAF, * ), WORK( * ), X( * )
32 * DOUBLE PRECISION RWORK( * )
33 * ..
34 *
35 *
36 *> \par Purpose:
37 * =============
38 *>
39 *> \verbatim
40 *>
41 *> ZLA_SYRCOND_X Computes the infinity norm condition number of
42 *> op(A) * diag(X) where X is a COMPLEX*16 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*16 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*16 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 ZSYTRF.
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 ZSYTRF.
92 *> \endverbatim
93 *>
94 *> \param[in] X
95 *> \verbatim
96 *> X is COMPLEX*16 array, dimension (N)
97 *> The vector X in the formula op(A) * diag(X).
98 *> \endverbatim
99 *>
100 *> \param[out] INFO
101 *> \verbatim
102 *> INFO is INTEGER
103 *> = 0: Successful exit.
104 *> i > 0: The ith argument is invalid.
105 *> \endverbatim
106 *>
107 *> \param[in] WORK
108 *> \verbatim
109 *> WORK is COMPLEX*16 array, dimension (2*N).
110 *> Workspace.
111 *> \endverbatim
112 *>
113 *> \param[in] RWORK
114 *> \verbatim
115 *> RWORK is DOUBLE PRECISION array, dimension (N).
116 *> Workspace.
117 *> \endverbatim
118 *
119 * Authors:
120 * ========
121 *
122 *> \author Univ. of Tennessee
123 *> \author Univ. of California Berkeley
124 *> \author Univ. of Colorado Denver
125 *> \author NAG Ltd.
126 *
127 *> \date September 2012
128 *
129 *> \ingroup complex16SYcomputational
130 *
131 * =====================================================================
132  DOUBLE PRECISION FUNCTION zla_syrcond_x( UPLO, N, A, LDA, AF,
133  $ ldaf, ipiv, x, info,
134  $ work, rwork )
135 *
136 * -- LAPACK computational routine (version 3.4.2) --
137 * -- LAPACK is a software package provided by Univ. of Tennessee, --
138 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139 * September 2012
140 *
141 * .. Scalar Arguments ..
142  CHARACTER uplo
143  INTEGER n, lda, ldaf, info
144 * ..
145 * .. Array Arguments ..
146  INTEGER ipiv( * )
147  COMPLEX*16 a( lda, * ), af( ldaf, * ), work( * ), x( * )
148  DOUBLE PRECISION rwork( * )
149 * ..
150 *
151 * =====================================================================
152 *
153 * .. Local Scalars ..
154  INTEGER kase
155  DOUBLE PRECISION ainvnm, anorm, tmp
156  INTEGER i, j
157  LOGICAL up, upper
158  COMPLEX*16 zdum
159 * ..
160 * .. Local Arrays ..
161  INTEGER isave( 3 )
162 * ..
163 * .. External Functions ..
164  LOGICAL lsame
165  EXTERNAL lsame
166 * ..
167 * .. External Subroutines ..
168  EXTERNAL zlacn2, zsytrs, xerbla
169 * ..
170 * .. Intrinsic Functions ..
171  INTRINSIC abs, max
172 * ..
173 * .. Statement Functions ..
174  DOUBLE PRECISION cabs1
175 * ..
176 * .. Statement Function Definitions ..
177  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
178 * ..
179 * .. Executable Statements ..
180 *
181  zla_syrcond_x = 0.0d+0
182 *
183  info = 0
184  upper = lsame( uplo, 'U' )
185  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
186  info = -1
187  ELSE IF( n.LT.0 ) THEN
188  info = -2
189  ELSE IF( lda.LT.max( 1, n ) ) THEN
190  info = -4
191  ELSE IF( ldaf.LT.max( 1, n ) ) THEN
192  info = -6
193  END IF
194  IF( info.NE.0 ) THEN
195  CALL xerbla( 'ZLA_SYRCOND_X', -info )
196  return
197  END IF
198  up = .false.
199  IF ( lsame( uplo, 'U' ) ) up = .true.
200 *
201 * Compute norm of op(A)*op2(C).
202 *
203  anorm = 0.0d+0
204  IF ( up ) THEN
205  DO i = 1, n
206  tmp = 0.0d+0
207  DO j = 1, i
208  tmp = tmp + cabs1( a( j, i ) * x( j ) )
209  END DO
210  DO j = i+1, n
211  tmp = tmp + cabs1( a( i, j ) * x( j ) )
212  END DO
213  rwork( i ) = tmp
214  anorm = max( anorm, tmp )
215  END DO
216  ELSE
217  DO i = 1, n
218  tmp = 0.0d+0
219  DO j = 1, i
220  tmp = tmp + cabs1( a( i, j ) * x( j ) )
221  END DO
222  DO j = i+1, n
223  tmp = tmp + cabs1( a( j, i ) * x( j ) )
224  END DO
225  rwork( i ) = tmp
226  anorm = max( anorm, tmp )
227  END DO
228  END IF
229 *
230 * Quick return if possible.
231 *
232  IF( n.EQ.0 ) THEN
233  zla_syrcond_x = 1.0d+0
234  return
235  ELSE IF( anorm .EQ. 0.0d+0 ) THEN
236  return
237  END IF
238 *
239 * Estimate the norm of inv(op(A)).
240 *
241  ainvnm = 0.0d+0
242 *
243  kase = 0
244  10 continue
245  CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
246  IF( kase.NE.0 ) THEN
247  IF( kase.EQ.2 ) THEN
248 *
249 * Multiply by R.
250 *
251  DO i = 1, n
252  work( i ) = work( i ) * rwork( i )
253  END DO
254 *
255  IF ( up ) THEN
256  CALL zsytrs( 'U', n, 1, af, ldaf, ipiv,
257  $ work, n, info )
258  ELSE
259  CALL zsytrs( 'L', n, 1, af, ldaf, ipiv,
260  $ work, n, info )
261  ENDIF
262 *
263 * Multiply by inv(X).
264 *
265  DO i = 1, n
266  work( i ) = work( i ) / x( i )
267  END DO
268  ELSE
269 *
270 * Multiply by inv(X**T).
271 *
272  DO i = 1, n
273  work( i ) = work( i ) / x( i )
274  END DO
275 *
276  IF ( up ) THEN
277  CALL zsytrs( 'U', n, 1, af, ldaf, ipiv,
278  $ work, n, info )
279  ELSE
280  CALL zsytrs( 'L', n, 1, af, ldaf, ipiv,
281  $ work, n, info )
282  END IF
283 *
284 * Multiply by R.
285 *
286  DO i = 1, n
287  work( i ) = work( i ) * rwork( i )
288  END DO
289  END IF
290  go to 10
291  END IF
292 *
293 * Compute the estimate of the reciprocal condition number.
294 *
295  IF( ainvnm .NE. 0.0d+0 )
296  $ zla_syrcond_x = 1.0d+0 / ainvnm
297 *
298  return
299 *
300  END