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