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