LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zpocon.f
Go to the documentation of this file.
1 *> \brief \b ZPOCON
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZPOCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zpocon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zpocon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zpocon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZPOCON( UPLO, N, A, LDA, ANORM, RCOND, WORK, RWORK,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER UPLO
26 * INTEGER INFO, LDA, N
27 * DOUBLE PRECISION ANORM, RCOND
28 * ..
29 * .. Array Arguments ..
30 * DOUBLE PRECISION RWORK( * )
31 * COMPLEX*16 A( LDA, * ), WORK( * )
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *> \verbatim
39 *>
40 *> ZPOCON estimates the reciprocal of the condition number (in the
41 *> 1-norm) of a complex Hermitian positive definite matrix using the
42 *> Cholesky factorization A = U**H*U or A = L*L**H computed by ZPOTRF.
43 *>
44 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
45 *> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] UPLO
52 *> \verbatim
53 *> UPLO is CHARACTER*1
54 *> = 'U': Upper triangle of A is stored;
55 *> = 'L': Lower triangle of A is stored.
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *> N is INTEGER
61 *> The order of the matrix A. N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in] A
65 *> \verbatim
66 *> A is COMPLEX*16 array, dimension (LDA,N)
67 *> The triangular factor U or L from the Cholesky factorization
68 *> A = U**H*U or A = L*L**H, as computed by ZPOTRF.
69 *> \endverbatim
70 *>
71 *> \param[in] LDA
72 *> \verbatim
73 *> LDA is INTEGER
74 *> The leading dimension of the array A. LDA >= max(1,N).
75 *> \endverbatim
76 *>
77 *> \param[in] ANORM
78 *> \verbatim
79 *> ANORM is DOUBLE PRECISION
80 *> The 1-norm (or infinity-norm) of the Hermitian matrix A.
81 *> \endverbatim
82 *>
83 *> \param[out] RCOND
84 *> \verbatim
85 *> RCOND is DOUBLE PRECISION
86 *> The reciprocal of the condition number of the matrix A,
87 *> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
88 *> estimate of the 1-norm of inv(A) computed in this routine.
89 *> \endverbatim
90 *>
91 *> \param[out] WORK
92 *> \verbatim
93 *> WORK is COMPLEX*16 array, dimension (2*N)
94 *> \endverbatim
95 *>
96 *> \param[out] RWORK
97 *> \verbatim
98 *> RWORK is DOUBLE PRECISION array, dimension (N)
99 *> \endverbatim
100 *>
101 *> \param[out] INFO
102 *> \verbatim
103 *> INFO is INTEGER
104 *> = 0: successful exit
105 *> < 0: if INFO = -i, the i-th argument had an illegal value
106 *> \endverbatim
107 *
108 * Authors:
109 * ========
110 *
111 *> \author Univ. of Tennessee
112 *> \author Univ. of California Berkeley
113 *> \author Univ. of Colorado Denver
114 *> \author NAG Ltd.
115 *
116 *> \date November 2011
117 *
118 *> \ingroup complex16POcomputational
119 *
120 * =====================================================================
121  SUBROUTINE zpocon( UPLO, N, A, LDA, ANORM, RCOND, WORK, RWORK,
122  $ info )
123 *
124 * -- LAPACK computational routine (version 3.4.0) --
125 * -- LAPACK is a software package provided by Univ. of Tennessee, --
126 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
127 * November 2011
128 *
129 * .. Scalar Arguments ..
130  CHARACTER UPLO
131  INTEGER INFO, LDA, N
132  DOUBLE PRECISION ANORM, RCOND
133 * ..
134 * .. Array Arguments ..
135  DOUBLE PRECISION RWORK( * )
136  COMPLEX*16 A( lda, * ), WORK( * )
137 * ..
138 *
139 * =====================================================================
140 *
141 * .. Parameters ..
142  DOUBLE PRECISION ONE, ZERO
143  parameter ( one = 1.0d+0, zero = 0.0d+0 )
144 * ..
145 * .. Local Scalars ..
146  LOGICAL UPPER
147  CHARACTER NORMIN
148  INTEGER IX, KASE
149  DOUBLE PRECISION AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
150  COMPLEX*16 ZDUM
151 * ..
152 * .. Local Arrays ..
153  INTEGER ISAVE( 3 )
154 * ..
155 * .. External Functions ..
156  LOGICAL LSAME
157  INTEGER IZAMAX
158  DOUBLE PRECISION DLAMCH
159  EXTERNAL lsame, izamax, dlamch
160 * ..
161 * .. External Subroutines ..
162  EXTERNAL xerbla, zdrscl, zlacn2, zlatrs
163 * ..
164 * .. Intrinsic Functions ..
165  INTRINSIC abs, dble, dimag, max
166 * ..
167 * .. Statement Functions ..
168  DOUBLE PRECISION CABS1
169 * ..
170 * .. Statement Function definitions ..
171  cabs1( zdum ) = abs( dble( zdum ) ) + abs( dimag( zdum ) )
172 * ..
173 * .. Executable Statements ..
174 *
175 * Test the input parameters.
176 *
177  info = 0
178  upper = lsame( uplo, 'U' )
179  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
180  info = -1
181  ELSE IF( n.LT.0 ) THEN
182  info = -2
183  ELSE IF( lda.LT.max( 1, n ) ) THEN
184  info = -4
185  ELSE IF( anorm.LT.zero ) THEN
186  info = -5
187  END IF
188  IF( info.NE.0 ) THEN
189  CALL xerbla( 'ZPOCON', -info )
190  RETURN
191  END IF
192 *
193 * Quick return if possible
194 *
195  rcond = zero
196  IF( n.EQ.0 ) THEN
197  rcond = one
198  RETURN
199  ELSE IF( anorm.EQ.zero ) THEN
200  RETURN
201  END IF
202 *
203  smlnum = dlamch( 'Safe minimum' )
204 *
205 * Estimate the 1-norm of inv(A).
206 *
207  kase = 0
208  normin = 'N'
209  10 CONTINUE
210  CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
211  IF( kase.NE.0 ) THEN
212  IF( upper ) THEN
213 *
214 * Multiply by inv(U**H).
215 *
216  CALL zlatrs( 'Upper', 'Conjugate transpose', 'Non-unit',
217  $ normin, n, a, lda, work, scalel, rwork, info )
218  normin = 'Y'
219 *
220 * Multiply by inv(U).
221 *
222  CALL zlatrs( 'Upper', 'No transpose', 'Non-unit', normin, n,
223  $ a, lda, work, scaleu, rwork, info )
224  ELSE
225 *
226 * Multiply by inv(L).
227 *
228  CALL zlatrs( 'Lower', 'No transpose', 'Non-unit', normin, n,
229  $ a, lda, work, scalel, rwork, info )
230  normin = 'Y'
231 *
232 * Multiply by inv(L**H).
233 *
234  CALL zlatrs( 'Lower', 'Conjugate transpose', 'Non-unit',
235  $ normin, n, a, lda, work, scaleu, rwork, info )
236  END IF
237 *
238 * Multiply by 1/SCALE if doing so will not cause overflow.
239 *
240  scale = scalel*scaleu
241  IF( scale.NE.one ) THEN
242  ix = izamax( n, work, 1 )
243  IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
244  $ GO TO 20
245  CALL zdrscl( n, scale, work, 1 )
246  END IF
247  GO TO 10
248  END IF
249 *
250 * Compute the estimate of the reciprocal condition number.
251 *
252  IF( ainvnm.NE.zero )
253  $ rcond = ( one / ainvnm ) / anorm
254 *
255  20 CONTINUE
256  RETURN
257 *
258 * End of ZPOCON
259 *
260  END
subroutine zdrscl(N, SA, SX, INCX)
ZDRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: zdrscl.f:86
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zlacn2(N, V, X, EST, KASE, ISAVE)
ZLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: zlacn2.f:135
subroutine zpocon(UPLO, N, A, LDA, ANORM, RCOND, WORK, RWORK, INFO)
ZPOCON
Definition: zpocon.f:123
subroutine zlatrs(UPLO, TRANS, DIAG, NORMIN, N, A, LDA, X, SCALE, CNORM, INFO)
ZLATRS solves a triangular system of equations with the scale factor set to prevent overflow...
Definition: zlatrs.f:241