LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
sppequ.f
Go to the documentation of this file.
1 *> \brief \b SPPEQU
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SPPEQU + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sppequ.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sppequ.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sppequ.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SPPEQU( UPLO, N, AP, S, SCOND, AMAX, INFO )
22 *
23 * .. Scalar Arguments ..
24 * CHARACTER UPLO
25 * INTEGER INFO, N
26 * REAL AMAX, SCOND
27 * ..
28 * .. Array Arguments ..
29 * REAL AP( * ), S( * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> SPPEQU computes row and column scalings intended to equilibrate a
39 *> symmetric positive definite matrix A in packed storage and reduce
40 *> its condition number (with respect to the two-norm). S contains the
41 *> scale factors, S(i)=1/sqrt(A(i,i)), chosen so that the scaled matrix
42 *> B with elements B(i,j)=S(i)*A(i,j)*S(j) has ones on the diagonal.
43 *> This choice of S puts the condition number of B within a factor N of
44 *> the smallest possible condition number over all possible diagonal
45 *> scalings.
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] UPLO
52 *> \verbatim
53 *> UPLO is CHARACTER*1
54 *> = 'U': Upper triangle of A is stored;
55 *> = 'L': Lower triangle of A is stored.
56 *> \endverbatim
57 *>
58 *> \param[in] N
59 *> \verbatim
60 *> N is INTEGER
61 *> The order of the matrix A. N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in] AP
65 *> \verbatim
66 *> AP is REAL array, dimension (N*(N+1)/2)
67 *> The upper or lower triangle of the symmetric matrix A, packed
68 *> columnwise in a linear array. The j-th column of A is stored
69 *> in the array AP as follows:
70 *> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
71 *> if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
72 *> \endverbatim
73 *>
74 *> \param[out] S
75 *> \verbatim
76 *> S is REAL array, dimension (N)
77 *> If INFO = 0, S contains the scale factors for A.
78 *> \endverbatim
79 *>
80 *> \param[out] SCOND
81 *> \verbatim
82 *> SCOND is REAL
83 *> If INFO = 0, S contains the ratio of the smallest S(i) to
84 *> the largest S(i). If SCOND >= 0.1 and AMAX is neither too
85 *> large nor too small, it is not worth scaling by S.
86 *> \endverbatim
87 *>
88 *> \param[out] AMAX
89 *> \verbatim
90 *> AMAX is REAL
91 *> Absolute value of largest matrix element. If AMAX is very
92 *> close to overflow or very close to underflow, the matrix
93 *> should be scaled.
94 *> \endverbatim
95 *>
96 *> \param[out] INFO
97 *> \verbatim
98 *> INFO is INTEGER
99 *> = 0: successful exit
100 *> < 0: if INFO = -i, the i-th argument had an illegal value
101 *> > 0: if INFO = i, the i-th diagonal element is nonpositive.
102 *> \endverbatim
103 *
104 * Authors:
105 * ========
106 *
107 *> \author Univ. of Tennessee
108 *> \author Univ. of California Berkeley
109 *> \author Univ. of Colorado Denver
110 *> \author NAG Ltd.
111 *
112 *> \date November 2011
113 *
114 *> \ingroup realOTHERcomputational
115 *
116 * =====================================================================
117  SUBROUTINE sppequ( UPLO, N, AP, S, SCOND, AMAX, INFO )
118 *
119 * -- LAPACK computational routine (version 3.4.0) --
120 * -- LAPACK is a software package provided by Univ. of Tennessee, --
121 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122 * November 2011
123 *
124 * .. Scalar Arguments ..
125  CHARACTER uplo
126  INTEGER info, n
127  REAL amax, scond
128 * ..
129 * .. Array Arguments ..
130  REAL ap( * ), s( * )
131 * ..
132 *
133 * =====================================================================
134 *
135 * .. Parameters ..
136  REAL one, zero
137  parameter( one = 1.0e+0, zero = 0.0e+0 )
138 * ..
139 * .. Local Scalars ..
140  LOGICAL upper
141  INTEGER i, jj
142  REAL smin
143 * ..
144 * .. External Functions ..
145  LOGICAL lsame
146  EXTERNAL lsame
147 * ..
148 * .. External Subroutines ..
149  EXTERNAL xerbla
150 * ..
151 * .. Intrinsic Functions ..
152  INTRINSIC max, min, sqrt
153 * ..
154 * .. Executable Statements ..
155 *
156 * Test the input parameters.
157 *
158  info = 0
159  upper = lsame( uplo, 'U' )
160  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
161  info = -1
162  ELSE IF( n.LT.0 ) THEN
163  info = -2
164  END IF
165  IF( info.NE.0 ) THEN
166  CALL xerbla( 'SPPEQU', -info )
167  return
168  END IF
169 *
170 * Quick return if possible
171 *
172  IF( n.EQ.0 ) THEN
173  scond = one
174  amax = zero
175  return
176  END IF
177 *
178 * Initialize SMIN and AMAX.
179 *
180  s( 1 ) = ap( 1 )
181  smin = s( 1 )
182  amax = s( 1 )
183 *
184  IF( upper ) THEN
185 *
186 * UPLO = 'U': Upper triangle of A is stored.
187 * Find the minimum and maximum diagonal elements.
188 *
189  jj = 1
190  DO 10 i = 2, n
191  jj = jj + i
192  s( i ) = ap( jj )
193  smin = min( smin, s( i ) )
194  amax = max( amax, s( i ) )
195  10 continue
196 *
197  ELSE
198 *
199 * UPLO = 'L': Lower triangle of A is stored.
200 * Find the minimum and maximum diagonal elements.
201 *
202  jj = 1
203  DO 20 i = 2, n
204  jj = jj + n - i + 2
205  s( i ) = ap( jj )
206  smin = min( smin, s( i ) )
207  amax = max( amax, s( i ) )
208  20 continue
209  END IF
210 *
211  IF( smin.LE.zero ) THEN
212 *
213 * Find the first non-positive diagonal element and return.
214 *
215  DO 30 i = 1, n
216  IF( s( i ).LE.zero ) THEN
217  info = i
218  return
219  END IF
220  30 continue
221  ELSE
222 *
223 * Set the scale factors to the reciprocals
224 * of the diagonal elements.
225 *
226  DO 40 i = 1, n
227  s( i ) = one / sqrt( s( i ) )
228  40 continue
229 *
230 * Compute SCOND = min(S(I)) / max(S(I))
231 *
232  scond = sqrt( smin ) / sqrt( amax )
233  END IF
234  return
235 *
236 * End of SPPEQU
237 *
238  END