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