LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dppcon.f
Go to the documentation of this file.
1 *> \brief \b DPPCON
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DPPCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dppcon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dppcon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dppcon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DPPCON( UPLO, N, AP, ANORM, RCOND, WORK, IWORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, N
26 * DOUBLE PRECISION ANORM, RCOND
27 * ..
28 * .. Array Arguments ..
29 * INTEGER IWORK( * )
30 * DOUBLE PRECISION AP( * ), WORK( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> DPPCON estimates the reciprocal of the condition number (in the
40 *> 1-norm) of a real symmetric positive definite packed matrix using
41 *> the Cholesky factorization A = U**T*U or A = L*L**T computed by
42 *> DPPTRF.
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] AP
65 *> \verbatim
66 *> AP is DOUBLE PRECISION array, dimension (N*(N+1)/2)
67 *> The triangular factor U or L from the Cholesky factorization
68 *> A = U**T*U or A = L*L**T, packed columnwise in a linear
69 *> array. The j-th column of U or L is stored in the array AP
70 *> as follows:
71 *> if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
72 *> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=n.
73 *> \endverbatim
74 *>
75 *> \param[in] ANORM
76 *> \verbatim
77 *> ANORM is DOUBLE PRECISION
78 *> The 1-norm (or infinity-norm) of the symmetric matrix A.
79 *> \endverbatim
80 *>
81 *> \param[out] RCOND
82 *> \verbatim
83 *> RCOND is DOUBLE PRECISION
84 *> The reciprocal of the condition number of the matrix A,
85 *> computed as RCOND = 1/(ANORM * AINVNM), where AINVNM is an
86 *> estimate of the 1-norm of inv(A) computed in this routine.
87 *> \endverbatim
88 *>
89 *> \param[out] WORK
90 *> \verbatim
91 *> WORK is DOUBLE PRECISION array, dimension (3*N)
92 *> \endverbatim
93 *>
94 *> \param[out] IWORK
95 *> \verbatim
96 *> IWORK is INTEGER array, dimension (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 doubleOTHERcomputational
117 *
118 * =====================================================================
119  SUBROUTINE dppcon( UPLO, N, AP, ANORM, RCOND, WORK, IWORK, 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 IWORK( * )
133  DOUBLE PRECISION 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  CHARACTER NORMIN
145  INTEGER IX, KASE
146  DOUBLE PRECISION AINVNM, SCALE, SCALEL, SCALEU, SMLNUM
147 * ..
148 * .. Local Arrays ..
149  INTEGER ISAVE( 3 )
150 * ..
151 * .. External Functions ..
152  LOGICAL LSAME
153  INTEGER IDAMAX
154  DOUBLE PRECISION DLAMCH
155  EXTERNAL lsame, idamax, dlamch
156 * ..
157 * .. External Subroutines ..
158  EXTERNAL dlacn2, dlatps, drscl, xerbla
159 * ..
160 * .. Intrinsic Functions ..
161  INTRINSIC abs
162 * ..
163 * .. Executable Statements ..
164 *
165 * Test the input parameters.
166 *
167  info = 0
168  upper = lsame( uplo, 'U' )
169  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
170  info = -1
171  ELSE IF( n.LT.0 ) THEN
172  info = -2
173  ELSE IF( anorm.LT.zero ) THEN
174  info = -4
175  END IF
176  IF( info.NE.0 ) THEN
177  CALL xerbla( 'DPPCON', -info )
178  RETURN
179  END IF
180 *
181 * Quick return if possible
182 *
183  rcond = zero
184  IF( n.EQ.0 ) THEN
185  rcond = one
186  RETURN
187  ELSE IF( anorm.EQ.zero ) THEN
188  RETURN
189  END IF
190 *
191  smlnum = dlamch( 'Safe minimum' )
192 *
193 * Estimate the 1-norm of the inverse.
194 *
195  kase = 0
196  normin = 'N'
197  10 CONTINUE
198  CALL dlacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
199  IF( kase.NE.0 ) THEN
200  IF( upper ) THEN
201 *
202 * Multiply by inv(U**T).
203 *
204  CALL dlatps( 'Upper', 'Transpose', 'Non-unit', normin, n,
205  $ ap, work, scalel, work( 2*n+1 ), info )
206  normin = 'Y'
207 *
208 * Multiply by inv(U).
209 *
210  CALL dlatps( 'Upper', 'No transpose', 'Non-unit', normin, n,
211  $ ap, work, scaleu, work( 2*n+1 ), info )
212  ELSE
213 *
214 * Multiply by inv(L).
215 *
216  CALL dlatps( 'Lower', 'No transpose', 'Non-unit', normin, n,
217  $ ap, work, scalel, work( 2*n+1 ), info )
218  normin = 'Y'
219 *
220 * Multiply by inv(L**T).
221 *
222  CALL dlatps( 'Lower', 'Transpose', 'Non-unit', normin, n,
223  $ ap, work, scaleu, work( 2*n+1 ), info )
224  END IF
225 *
226 * Multiply by 1/SCALE if doing so will not cause overflow.
227 *
228  scale = scalel*scaleu
229  IF( scale.NE.one ) THEN
230  ix = idamax( n, work, 1 )
231  IF( scale.LT.abs( work( ix ) )*smlnum .OR. scale.EQ.zero )
232  $ GO TO 20
233  CALL drscl( n, scale, work, 1 )
234  END IF
235  GO TO 10
236  END IF
237 *
238 * Compute the estimate of the reciprocal condition number.
239 *
240  IF( ainvnm.NE.zero )
241  $ rcond = ( one / ainvnm ) / anorm
242 *
243  20 CONTINUE
244  RETURN
245 *
246 * End of DPPCON
247 *
248  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine drscl(N, SA, SX, INCX)
DRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: drscl.f:86
subroutine dlatps(UPLO, TRANS, DIAG, NORMIN, N, AP, X, SCALE, CNORM, INFO)
DLATPS solves a triangular system of equations with the matrix held in packed storage.
Definition: dlatps.f:231
subroutine dppcon(UPLO, N, AP, ANORM, RCOND, WORK, IWORK, INFO)
DPPCON
Definition: dppcon.f:120
subroutine dlacn2(N, V, X, ISGN, EST, KASE, ISAVE)
DLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: dlacn2.f:138