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