LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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[in] WORK
116 *> \verbatim
117 *> WORK is REAL array, dimension (3*N).
118 *> Workspace.
119 *> \endverbatim
120 *>
121 *> \param[in] 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 *> \date September 2012
136 *
137 *> \ingroup realPOcomputational
138 *
139 * =====================================================================
140  REAL FUNCTION sla_porcond( UPLO, N, A, LDA, AF, LDAF, CMODE, C,
141  $ info, work, iwork )
142 *
143 * -- LAPACK computational routine (version 3.4.2) --
144 * -- LAPACK is a software package provided by Univ. of Tennessee, --
145 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
146 * September 2012
147 *
148 * .. Scalar Arguments ..
149  CHARACTER UPLO
150  INTEGER N, LDA, LDAF, INFO, CMODE
151  REAL A( lda, * ), AF( ldaf, * ), WORK( * ),
152  $ c( * )
153 * ..
154 * .. Array Arguments ..
155  INTEGER IWORK( * )
156 * ..
157 *
158 * =====================================================================
159 *
160 * .. Local Scalars ..
161  INTEGER KASE, I, J
162  REAL AINVNM, TMP
163  LOGICAL UP
164 * ..
165 * .. Array Arguments ..
166  INTEGER ISAVE( 3 )
167 * ..
168 * .. External Functions ..
169  LOGICAL LSAME
170  INTEGER ISAMAX
171  EXTERNAL lsame, isamax
172 * ..
173 * .. External Subroutines ..
174  EXTERNAL slacn2, spotrs, xerbla
175 * ..
176 * .. Intrinsic Functions ..
177  INTRINSIC abs, max
178 * ..
179 * .. Executable Statements ..
180 *
181  sla_porcond = 0.0
182 *
183  info = 0
184  IF( n.LT.0 ) THEN
185  info = -2
186  END IF
187  IF( info.NE.0 ) THEN
188  CALL xerbla( 'SLA_PORCOND', -info )
189  RETURN
190  END IF
191 
192  IF( n.EQ.0 ) THEN
193  sla_porcond = 1.0
194  RETURN
195  END IF
196  up = .false.
197  IF ( lsame( uplo, 'U' ) ) up = .true.
198 *
199 * Compute the equilibration matrix R such that
200 * inv(R)*A*C has unit 1-norm.
201 *
202  IF ( up ) THEN
203  DO i = 1, n
204  tmp = 0.0
205  IF ( cmode .EQ. 1 ) THEN
206  DO j = 1, i
207  tmp = tmp + abs( a( j, i ) * c( j ) )
208  END DO
209  DO j = i+1, n
210  tmp = tmp + abs( a( i, j ) * c( j ) )
211  END DO
212  ELSE IF ( cmode .EQ. 0 ) THEN
213  DO j = 1, i
214  tmp = tmp + abs( a( j, i ) )
215  END DO
216  DO j = i+1, n
217  tmp = tmp + abs( a( i, j ) )
218  END DO
219  ELSE
220  DO j = 1, i
221  tmp = tmp + abs( a( j ,i ) / c( j ) )
222  END DO
223  DO j = i+1, n
224  tmp = tmp + abs( a( i, j ) / c( j ) )
225  END DO
226  END IF
227  work( 2*n+i ) = tmp
228  END DO
229  ELSE
230  DO i = 1, n
231  tmp = 0.0
232  IF ( cmode .EQ. 1 ) THEN
233  DO j = 1, i
234  tmp = tmp + abs( a( i, j ) * c( j ) )
235  END DO
236  DO j = i+1, n
237  tmp = tmp + abs( a( j, i ) * c( j ) )
238  END DO
239  ELSE IF ( cmode .EQ. 0 ) THEN
240  DO j = 1, i
241  tmp = tmp + abs( a( i, j ) )
242  END DO
243  DO j = i+1, n
244  tmp = tmp + abs( a( j, i ) )
245  END DO
246  ELSE
247  DO j = 1, i
248  tmp = tmp + abs( a( i, j ) / c( j ) )
249  END DO
250  DO j = i+1, n
251  tmp = tmp + abs( a( j, i ) / c( j ) )
252  END DO
253  END IF
254  work( 2*n+i ) = tmp
255  END DO
256  ENDIF
257 *
258 * Estimate the norm of inv(op(A)).
259 *
260  ainvnm = 0.0
261 
262  kase = 0
263  10 CONTINUE
264  CALL slacn2( n, work( n+1 ), work, iwork, ainvnm, kase, isave )
265  IF( kase.NE.0 ) THEN
266  IF( kase.EQ.2 ) THEN
267 *
268 * Multiply by R.
269 *
270  DO i = 1, n
271  work( i ) = work( i ) * work( 2*n+i )
272  END DO
273 
274  IF (up) THEN
275  CALL spotrs( 'Upper', n, 1, af, ldaf, work, n, info )
276  ELSE
277  CALL spotrs( 'Lower', n, 1, af, ldaf, work, n, info )
278  ENDIF
279 *
280 * Multiply by inv(C).
281 *
282  IF ( cmode .EQ. 1 ) THEN
283  DO i = 1, n
284  work( i ) = work( i ) / c( i )
285  END DO
286  ELSE IF ( cmode .EQ. -1 ) THEN
287  DO i = 1, n
288  work( i ) = work( i ) * c( i )
289  END DO
290  END IF
291  ELSE
292 *
293 * Multiply by inv(C**T).
294 *
295  IF ( cmode .EQ. 1 ) THEN
296  DO i = 1, n
297  work( i ) = work( i ) / c( i )
298  END DO
299  ELSE IF ( cmode .EQ. -1 ) THEN
300  DO i = 1, n
301  work( i ) = work( i ) * c( i )
302  END DO
303  END IF
304 
305  IF ( up ) THEN
306  CALL spotrs( 'Upper', n, 1, af, ldaf, work, n, info )
307  ELSE
308  CALL spotrs( 'Lower', n, 1, af, ldaf, work, n, info )
309  ENDIF
310 *
311 * Multiply by R.
312 *
313  DO i = 1, n
314  work( i ) = work( i ) * work( 2*n+i )
315  END DO
316  END IF
317  GO TO 10
318  END IF
319 *
320 * Compute the estimate of the reciprocal condition number.
321 *
322  IF( ainvnm .NE. 0.0 )
323  $ sla_porcond = ( 1.0 / ainvnm )
324 *
325  RETURN
326 *
327  END
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...
Definition: sla_porcond.f:142
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
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:138
subroutine spotrs(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
SPOTRS
Definition: spotrs.f:112