LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zhpcon.f
Go to the documentation of this file.
1 *> \brief \b ZHPCON
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZHPCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zhpcon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zhpcon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zhpcon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZHPCON( UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, N
26 * DOUBLE PRECISION ANORM, RCOND
27 * ..
28 * .. Array Arguments ..
29 * INTEGER IPIV( * )
30 * COMPLEX*16 AP( * ), WORK( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> ZHPCON estimates the reciprocal of the condition number of a complex
40 *> Hermitian packed matrix A using the factorization A = U*D*U**H or
41 *> A = L*D*L**H computed by ZHPTRF.
42 *>
43 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
44 *> condition number is computed as RCOND = 1 / (ANORM * norm(inv(A))).
45 *> \endverbatim
46 *
47 * Arguments:
48 * ==========
49 *
50 *> \param[in] UPLO
51 *> \verbatim
52 *> UPLO is CHARACTER*1
53 *> Specifies whether the details of the factorization are stored
54 *> as an upper or lower triangular matrix.
55 *> = 'U': Upper triangular, form is A = U*D*U**H;
56 *> = 'L': Lower triangular, form is A = L*D*L**H.
57 *> \endverbatim
58 *>
59 *> \param[in] N
60 *> \verbatim
61 *> N is INTEGER
62 *> The order of the matrix A. N >= 0.
63 *> \endverbatim
64 *>
65 *> \param[in] AP
66 *> \verbatim
67 *> AP is COMPLEX*16 array, dimension (N*(N+1)/2)
68 *> The block diagonal matrix D and the multipliers used to
69 *> obtain the factor U or L as computed by ZHPTRF, stored as a
70 *> packed triangular matrix.
71 *> \endverbatim
72 *>
73 *> \param[in] IPIV
74 *> \verbatim
75 *> IPIV is INTEGER array, dimension (N)
76 *> Details of the interchanges and the block structure of D
77 *> as determined by ZHPTRF.
78 *> \endverbatim
79 *>
80 *> \param[in] ANORM
81 *> \verbatim
82 *> ANORM is DOUBLE PRECISION
83 *> The 1-norm of the original matrix A.
84 *> \endverbatim
85 *>
86 *> \param[out] RCOND
87 *> \verbatim
88 *> RCOND is DOUBLE PRECISION
89 *> The reciprocal of the condition number of the matrix A,
90 *> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
91 *> estimate of the 1-norm of inv(A) computed in this routine.
92 *> \endverbatim
93 *>
94 *> \param[out] WORK
95 *> \verbatim
96 *> WORK is COMPLEX*16 array, dimension (2*N)
97 *> \endverbatim
98 *>
99 *> \param[out] INFO
100 *> \verbatim
101 *> INFO is INTEGER
102 *> = 0: successful exit
103 *> < 0: if INFO = -i, the i-th argument had an illegal value
104 *> \endverbatim
105 *
106 * Authors:
107 * ========
108 *
109 *> \author Univ. of Tennessee
110 *> \author Univ. of California Berkeley
111 *> \author Univ. of Colorado Denver
112 *> \author NAG Ltd.
113 *
114 *> \date November 2011
115 *
116 *> \ingroup complex16OTHERcomputational
117 *
118 * =====================================================================
119  SUBROUTINE zhpcon( UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO )
120 *
121 * -- LAPACK computational routine (version 3.4.0) --
122 * -- LAPACK is a software package provided by Univ. of Tennessee, --
123 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
124 * November 2011
125 *
126 * .. Scalar Arguments ..
127  CHARACTER UPLO
128  INTEGER INFO, N
129  DOUBLE PRECISION ANORM, RCOND
130 * ..
131 * .. Array Arguments ..
132  INTEGER IPIV( * )
133  COMPLEX*16 AP( * ), WORK( * )
134 * ..
135 *
136 * =====================================================================
137 *
138 * .. Parameters ..
139  DOUBLE PRECISION ONE, ZERO
140  parameter ( one = 1.0d+0, zero = 0.0d+0 )
141 * ..
142 * .. Local Scalars ..
143  LOGICAL UPPER
144  INTEGER I, IP, KASE
145  DOUBLE PRECISION AINVNM
146 * ..
147 * .. Local Arrays ..
148  INTEGER ISAVE( 3 )
149 * ..
150 * .. External Functions ..
151  LOGICAL LSAME
152  EXTERNAL lsame
153 * ..
154 * .. External Subroutines ..
155  EXTERNAL xerbla, zhptrs, zlacn2
156 * ..
157 * .. Executable Statements ..
158 *
159 * Test the input parameters.
160 *
161  info = 0
162  upper = lsame( uplo, 'U' )
163  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
164  info = -1
165  ELSE IF( n.LT.0 ) THEN
166  info = -2
167  ELSE IF( anorm.LT.zero ) THEN
168  info = -5
169  END IF
170  IF( info.NE.0 ) THEN
171  CALL xerbla( 'ZHPCON', -info )
172  RETURN
173  END IF
174 *
175 * Quick return if possible
176 *
177  rcond = zero
178  IF( n.EQ.0 ) THEN
179  rcond = one
180  RETURN
181  ELSE IF( anorm.LE.zero ) THEN
182  RETURN
183  END IF
184 *
185 * Check that the diagonal matrix D is nonsingular.
186 *
187  IF( upper ) THEN
188 *
189 * Upper triangular storage: examine D from bottom to top
190 *
191  ip = n*( n+1 ) / 2
192  DO 10 i = n, 1, -1
193  IF( ipiv( i ).GT.0 .AND. ap( ip ).EQ.zero )
194  $ RETURN
195  ip = ip - i
196  10 CONTINUE
197  ELSE
198 *
199 * Lower triangular storage: examine D from top to bottom.
200 *
201  ip = 1
202  DO 20 i = 1, n
203  IF( ipiv( i ).GT.0 .AND. ap( ip ).EQ.zero )
204  $ RETURN
205  ip = ip + n - i + 1
206  20 CONTINUE
207  END IF
208 *
209 * Estimate the 1-norm of the inverse.
210 *
211  kase = 0
212  30 CONTINUE
213  CALL zlacn2( n, work( n+1 ), work, ainvnm, kase, isave )
214  IF( kase.NE.0 ) THEN
215 *
216 * Multiply by inv(L*D*L**H) or inv(U*D*U**H).
217 *
218  CALL zhptrs( uplo, n, 1, ap, ipiv, work, n, info )
219  GO TO 30
220  END IF
221 *
222 * Compute the estimate of the reciprocal condition number.
223 *
224  IF( ainvnm.NE.zero )
225  $ rcond = ( one / ainvnm ) / anorm
226 *
227  RETURN
228 *
229 * End of ZHPCON
230 *
231  END
subroutine zhptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZHPTRS
Definition: zhptrs.f:117
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 zhpcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
ZHPCON
Definition: zhpcon.f:120