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