LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sla_porcond.f
Go to the documentation of this file.
1*> \brief \b SLA_PORCOND estimates the Skeel condition number for a symmetric positive-definite matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SLA_PORCOND + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sla_porcond.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sla_porcond.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sla_porcond.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* REAL FUNCTION SLA_PORCOND( UPLO, N, A, LDA, AF, LDAF, CMODE, C,
22* INFO, WORK, IWORK )
23*
24* .. Scalar Arguments ..
25* CHARACTER UPLO
26* INTEGER N, LDA, LDAF, INFO, CMODE
27* REAL A( LDA, * ), AF( LDAF, * ), WORK( * ),
28* $ C( * )
29* ..
30* .. Array Arguments ..
31* INTEGER IWORK( * )
32* ..
33*
34*
35*> \par Purpose:
36* =============
37*>
38*> \verbatim
39*>
40*> SLA_PORCOND Estimates the Skeel condition number of op(A) * op2(C)
41*> where op2 is determined by CMODE as follows
42*> CMODE = 1 op2(C) = C
43*> CMODE = 0 op2(C) = I
44*> CMODE = -1 op2(C) = inv(C)
45*> The Skeel condition number cond(A) = norminf( |inv(A)||A| )
46*> is computed by computing scaling factors R such that
47*> diag(R)*A*op2(C) is row equilibrated and computing the standard
48*> infinity-norm condition number.
49*> \endverbatim
50*
51* Arguments:
52* ==========
53*
54*> \param[in] UPLO
55*> \verbatim
56*> UPLO is CHARACTER*1
57*> = 'U': Upper triangle of A is stored;
58*> = 'L': Lower triangle of A is stored.
59*> \endverbatim
60*>
61*> \param[in] N
62*> \verbatim
63*> N is INTEGER
64*> The number of linear equations, i.e., the order of the
65*> matrix A. N >= 0.
66*> \endverbatim
67*>
68*> \param[in] A
69*> \verbatim
70*> A is REAL array, dimension (LDA,N)
71*> On entry, the N-by-N matrix A.
72*> \endverbatim
73*>
74*> \param[in] LDA
75*> \verbatim
76*> LDA is INTEGER
77*> The leading dimension of the array A. LDA >= max(1,N).
78*> \endverbatim
79*>
80*> \param[in] AF
81*> \verbatim
82*> AF is REAL array, dimension (LDAF,N)
83*> The triangular factor U or L from the Cholesky factorization
84*> A = U**T*U or A = L*L**T, as computed by SPOTRF.
85*> \endverbatim
86*>
87*> \param[in] LDAF
88*> \verbatim
89*> LDAF is INTEGER
90*> The leading dimension of the array AF. LDAF >= max(1,N).
91*> \endverbatim
92*>
93*> \param[in] CMODE
94*> \verbatim
95*> CMODE is INTEGER
96*> Determines op2(C) in the formula op(A) * op2(C) as follows:
97*> CMODE = 1 op2(C) = C
98*> CMODE = 0 op2(C) = I
99*> CMODE = -1 op2(C) = inv(C)
100*> \endverbatim
101*>
102*> \param[in] C
103*> \verbatim
104*> C is REAL array, dimension (N)
105*> The vector C in the formula op(A) * op2(C).
106*> \endverbatim
107*>
108*> \param[out] INFO
109*> \verbatim
110*> INFO is INTEGER
111*> = 0: Successful exit.
112*> i > 0: The ith argument is invalid.
113*> \endverbatim
114*>
115*> \param[out] WORK
116*> \verbatim
117*> WORK is REAL array, dimension (3*N).
118*> Workspace.
119*> \endverbatim
120*>
121*> \param[out] IWORK
122*> \verbatim
123*> IWORK is INTEGER array, dimension (N).
124*> Workspace.
125*> \endverbatim
126*
127* Authors:
128* ========
129*
130*> \author Univ. of Tennessee
131*> \author Univ. of California Berkeley
132*> \author Univ. of Colorado Denver
133*> \author NAG Ltd.
134*
135*> \ingroup la_porcond
136*
137* =====================================================================
138 REAL function sla_porcond( uplo, n, a, lda, af, ldaf, cmode, c,
139 $ info, work, iwork )
140*
141* -- LAPACK computational routine --
142* -- LAPACK is a software package provided by Univ. of Tennessee, --
143* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
144*
145* .. Scalar Arguments ..
146 CHARACTER uplo
147 INTEGER n, lda, ldaf, info, cmode
148 REAL a( lda, * ), af( ldaf, * ), work( * ),
149 $ c( * )
150* ..
151* .. Array Arguments ..
152 INTEGER iwork( * )
153* ..
154*
155* =====================================================================
156*
157* .. Local Scalars ..
158 INTEGER kase, i, j
159 REAL ainvnm, tmp
160 LOGICAL up
161* ..
162* .. Array Arguments ..
163 INTEGER isave( 3 )
164* ..
165* .. External Functions ..
166 LOGICAL lsame
167 EXTERNAL lsame
168* ..
169* .. External Subroutines ..
170 EXTERNAL slacn2, spotrs, xerbla
171* ..
172* .. Intrinsic Functions ..
173 INTRINSIC abs, max
174* ..
175* .. Executable Statements ..
176*
177 sla_porcond = 0.0
178*
179 info = 0
180 IF( n.LT.0 ) THEN
181 info = -2
182 END IF
183 IF( info.NE.0 ) THEN
184 CALL xerbla( 'SLA_PORCOND', -info )
185 RETURN
186 END IF
187
188 IF( n.EQ.0 ) THEN
189 sla_porcond = 1.0
190 RETURN
191 END IF
192 up = .false.
193 IF ( lsame( uplo, 'U' ) ) up = .true.
194*
195* Compute the equilibration matrix R such that
196* inv(R)*A*C has unit 1-norm.
197*
198 IF ( up ) THEN
199 DO i = 1, n
200 tmp = 0.0
201 IF ( cmode .EQ. 1 ) THEN
202 DO j = 1, i
203 tmp = tmp + abs( a( j, i ) * c( j ) )
204 END DO
205 DO j = i+1, n
206 tmp = tmp + abs( a( i, j ) * c( j ) )
207 END DO
208 ELSE IF ( cmode .EQ. 0 ) THEN
209 DO j = 1, i
210 tmp = tmp + abs( a( j, i ) )
211 END DO
212 DO j = i+1, n
213 tmp = tmp + abs( a( i, j ) )
214 END DO
215 ELSE
216 DO j = 1, i
217 tmp = tmp + abs( a( j ,i ) / c( j ) )
218 END DO
219 DO j = i+1, n
220 tmp = tmp + abs( a( i, j ) / c( j ) )
221 END DO
222 END IF
223 work( 2*n+i ) = tmp
224 END DO
225 ELSE
226 DO i = 1, n
227 tmp = 0.0
228 IF ( cmode .EQ. 1 ) THEN
229 DO j = 1, i
230 tmp = tmp + abs( a( i, j ) * c( j ) )
231 END DO
232 DO j = i+1, n
233 tmp = tmp + abs( a( j, i ) * c( j ) )
234 END DO
235 ELSE IF ( cmode .EQ. 0 ) THEN
236 DO j = 1, i
237 tmp = tmp + abs( a( i, j ) )
238 END DO
239 DO j = i+1, n
240 tmp = tmp + abs( a( j, i ) )
241 END DO
242 ELSE
243 DO j = 1, i
244 tmp = tmp + abs( a( i, j ) / c( j ) )
245 END DO
246 DO j = i+1, n
247 tmp = tmp + abs( a( j, i ) / c( j ) )
248 END DO
249 END IF
250 work( 2*n+i ) = tmp
251 END DO
252 ENDIF
253*
254* Estimate the norm of inv(op(A)).
255*
256 ainvnm = 0.0
257
258 kase = 0
259 10 CONTINUE
260 CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
261 IF( kase.NE.0 ) THEN
262 IF( kase.EQ.2 ) THEN
263*
264* Multiply by R.
265*
266 DO i = 1, n
267 work( i ) = work( i ) * work( 2*n+i )
268 END DO
269
270 IF (up) THEN
271 CALL spotrs( 'Upper', n, 1, af, ldaf, work, n, info )
272 ELSE
273 CALL spotrs( 'Lower', n, 1, af, ldaf, work, n, info )
274 ENDIF
275*
276* Multiply by inv(C).
277*
278 IF ( cmode .EQ. 1 ) THEN
279 DO i = 1, n
280 work( i ) = work( i ) / c( i )
281 END DO
282 ELSE IF ( cmode .EQ. -1 ) THEN
283 DO i = 1, n
284 work( i ) = work( i ) * c( i )
285 END DO
286 END IF
287 ELSE
288*
289* Multiply by inv(C**T).
290*
291 IF ( cmode .EQ. 1 ) THEN
292 DO i = 1, n
293 work( i ) = work( i ) / c( i )
294 END DO
295 ELSE IF ( cmode .EQ. -1 ) THEN
296 DO i = 1, n
297 work( i ) = work( i ) * c( i )
298 END DO
299 END IF
300
301 IF ( up ) THEN
302 CALL spotrs( 'Upper', n, 1, af, ldaf, work, n, info )
303 ELSE
304 CALL spotrs( 'Lower', n, 1, af, ldaf, work, n, info )
305 ENDIF
306*
307* Multiply by R.
308*
309 DO i = 1, n
310 work( i ) = work( i ) * work( 2*n+i )
311 END DO
312 END IF
313 GO TO 10
314 END IF
315*
316* Compute the estimate of the reciprocal condition number.
317*
318 IF( ainvnm .NE. 0.0 )
319 $ sla_porcond = ( 1.0 / ainvnm )
320*
321 RETURN
322*
323* End of SLA_PORCOND
324*
325 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
real function sla_porcond(uplo, n, a, lda, af, ldaf, cmode, c, info, work, iwork)
SLA_PORCOND estimates the Skeel condition number for a symmetric positive-definite matrix.
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
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine spotrs(uplo, n, nrhs, a, lda, b, ldb, info)
SPOTRS
Definition spotrs.f:110