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