LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ssycon_rook.f
Go to the documentation of this file.
1*> \brief <b> SSYCON_ROOK </b>
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SSYCON_ROOK + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssycon_rook.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssycon_rook.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssycon_rook.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE SSYCON_ROOK( UPLO, N, A, LDA, IPIV, ANORM, RCOND,
22* WORK, 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_ROOK 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_ROOK.
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_ROOK.
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_ROOK.
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_rook
126*
127*> \par Contributors:
128* ==================
129*> \verbatim
130*>
131*> December 2016, Igor Kozachenko,
132*> Computer Science Division,
133*> University of California, Berkeley
134*>
135*> September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
136*> School of Mathematics,
137*> University of Manchester
138*>
139*> \endverbatim
140*
141* =====================================================================
142 SUBROUTINE ssycon_rook( UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK,
143 $ IWORK, INFO )
144*
145* -- LAPACK computational routine --
146* -- LAPACK is a software package provided by Univ. of Tennessee, --
147* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
148*
149* .. Scalar Arguments ..
150 CHARACTER UPLO
151 INTEGER INFO, LDA, N
152 REAL ANORM, RCOND
153* ..
154* .. Array Arguments ..
155 INTEGER IPIV( * ), IWORK( * )
156 REAL A( LDA, * ), WORK( * )
157* ..
158*
159* =====================================================================
160*
161* .. Parameters ..
162 REAL ONE, ZERO
163 parameter( one = 1.0e+0, zero = 0.0e+0 )
164* ..
165* .. Local Scalars ..
166 LOGICAL UPPER
167 INTEGER I, KASE
168 REAL AINVNM
169* ..
170* .. Local Arrays ..
171 INTEGER ISAVE( 3 )
172* ..
173* .. External Functions ..
174 LOGICAL LSAME
175 EXTERNAL lsame
176* ..
177* .. External Subroutines ..
178 EXTERNAL slacn2, ssytrs_rook, xerbla
179* ..
180* .. Intrinsic Functions ..
181 INTRINSIC max
182* ..
183* .. Executable Statements ..
184*
185* Test the input parameters.
186*
187 info = 0
188 upper = lsame( uplo, 'U' )
189 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
190 info = -1
191 ELSE IF( n.LT.0 ) THEN
192 info = -2
193 ELSE IF( lda.LT.max( 1, n ) ) THEN
194 info = -4
195 ELSE IF( anorm.LT.zero ) THEN
196 info = -6
197 END IF
198 IF( info.NE.0 ) THEN
199 CALL xerbla( 'SSYCON_ROOK', -info )
200 RETURN
201 END IF
202*
203* Quick return if possible
204*
205 rcond = zero
206 IF( n.EQ.0 ) THEN
207 rcond = one
208 RETURN
209 ELSE IF( anorm.LE.zero ) THEN
210 RETURN
211 END IF
212*
213* Check that the diagonal matrix D is nonsingular.
214*
215 IF( upper ) THEN
216*
217* Upper triangular storage: examine D from bottom to top
218*
219 DO 10 i = n, 1, -1
220 IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
221 $ RETURN
222 10 CONTINUE
223 ELSE
224*
225* Lower triangular storage: examine D from top to bottom.
226*
227 DO 20 i = 1, n
228 IF( ipiv( i ).GT.0 .AND. a( i, i ).EQ.zero )
229 $ RETURN
230 20 CONTINUE
231 END IF
232*
233* Estimate the 1-norm of the inverse.
234*
235 kase = 0
236 30 CONTINUE
237 CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
238 IF( kase.NE.0 ) THEN
239*
240* Multiply by inv(L*D*L**T) or inv(U*D*U**T).
241*
242 CALL ssytrs_rook( uplo, n, 1, a, lda, ipiv, work, n, info )
243 GO TO 30
244 END IF
245*
246* Compute the estimate of the reciprocal condition number.
247*
248 IF( ainvnm.NE.zero )
249 $ rcond = ( one / ainvnm ) / anorm
250*
251 RETURN
252*
253* End of SSYCON_ROOK
254*
255 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssycon_rook(uplo, n, a, lda, ipiv, anorm, rcond, work, iwork, info)
SSYCON_ROOK
subroutine ssytrs_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, info)
SSYTRS_ROOK
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