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