LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
claqhb.f
Go to the documentation of this file.
1*> \brief \b CLAQHB scales a Hermitian band matrix, using scaling factors computed by cpbequ.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CLAQHB + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claqhb.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claqhb.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claqhb.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE CLAQHB( UPLO, N, KD, AB, LDAB, S, SCOND, AMAX, EQUED )
22*
23* .. Scalar Arguments ..
24* CHARACTER EQUED, UPLO
25* INTEGER 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*> CLAQHB equilibrates an Hermitian band matrix A using the scaling
40*> factors in the vector S.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] UPLO
47*> \verbatim
48*> UPLO is CHARACTER*1
49*> Specifies whether the upper or lower triangular part of the
50*> symmetric matrix A is stored.
51*> = 'U': Upper triangular
52*> = 'L': Lower triangular
53*> \endverbatim
54*>
55*> \param[in] N
56*> \verbatim
57*> N is INTEGER
58*> The order of the matrix A. N >= 0.
59*> \endverbatim
60*>
61*> \param[in] KD
62*> \verbatim
63*> KD is INTEGER
64*> The number of super-diagonals of the matrix A if UPLO = 'U',
65*> or the number of sub-diagonals if UPLO = 'L'. KD >= 0.
66*> \endverbatim
67*>
68*> \param[in,out] AB
69*> \verbatim
70*> AB is COMPLEX array, dimension (LDAB,N)
71*> On entry, the upper or lower triangle of the symmetric band
72*> matrix A, stored in the first KD+1 rows of the array. The
73*> j-th column of A is stored in the j-th column of the array AB
74*> as follows:
75*> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
76*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
77*>
78*> On exit, if INFO = 0, the triangular factor U or L from the
79*> Cholesky factorization A = U**H *U or A = L*L**H of the band
80*> matrix A, in the same storage format as A.
81*> \endverbatim
82*>
83*> \param[in] LDAB
84*> \verbatim
85*> LDAB is INTEGER
86*> The leading dimension of the array AB. LDAB >= KD+1.
87*> \endverbatim
88*>
89*> \param[out] S
90*> \verbatim
91*> S is REAL array, dimension (N)
92*> The scale factors for A.
93*> \endverbatim
94*>
95*> \param[in] SCOND
96*> \verbatim
97*> SCOND is REAL
98*> Ratio of the smallest S(i) to the largest S(i).
99*> \endverbatim
100*>
101*> \param[in] AMAX
102*> \verbatim
103*> AMAX is REAL
104*> Absolute value of largest matrix entry.
105*> \endverbatim
106*>
107*> \param[out] EQUED
108*> \verbatim
109*> EQUED is CHARACTER*1
110*> Specifies whether or not equilibration was done.
111*> = 'N': No equilibration.
112*> = 'Y': Equilibration was done, i.e., A has been replaced by
113*> diag(S) * A * diag(S).
114*> \endverbatim
115*
116*> \par Internal Parameters:
117* =========================
118*>
119*> \verbatim
120*> THRESH is a threshold value used to decide if scaling should be done
121*> based on the ratio of the scaling factors. If SCOND < THRESH,
122*> scaling is done.
123*>
124*> LARGE and SMALL are threshold values used to decide if scaling should
125*> be done based on the absolute size of the largest matrix element.
126*> If AMAX > LARGE or AMAX < SMALL, scaling is done.
127*> \endverbatim
128*
129* Authors:
130* ========
131*
132*> \author Univ. of Tennessee
133*> \author Univ. of California Berkeley
134*> \author Univ. of Colorado Denver
135*> \author NAG Ltd.
136*
137*> \ingroup laqhb
138*
139* =====================================================================
140 SUBROUTINE claqhb( UPLO, N, KD, AB, LDAB, S, SCOND, AMAX, EQUED )
141*
142* -- LAPACK auxiliary routine --
143* -- LAPACK is a software package provided by Univ. of Tennessee, --
144* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145*
146* .. Scalar Arguments ..
147 CHARACTER EQUED, UPLO
148 INTEGER KD, LDAB, N
149 REAL AMAX, SCOND
150* ..
151* .. Array Arguments ..
152 REAL S( * )
153 COMPLEX AB( LDAB, * )
154* ..
155*
156* =====================================================================
157*
158* .. Parameters ..
159 REAL ONE, THRESH
160 parameter( one = 1.0e+0, thresh = 0.1e+0 )
161* ..
162* .. Local Scalars ..
163 INTEGER I, J
164 REAL CJ, LARGE, SMALL
165* ..
166* .. External Functions ..
167 LOGICAL LSAME
168 REAL SLAMCH
169 EXTERNAL lsame, slamch
170* ..
171* .. Intrinsic Functions ..
172 INTRINSIC max, min, real
173* ..
174* .. Executable Statements ..
175*
176* Quick return if possible
177*
178 IF( n.LE.0 ) THEN
179 equed = 'N'
180 RETURN
181 END IF
182*
183* Initialize LARGE and SMALL.
184*
185 small = slamch( 'Safe minimum' ) / slamch( 'Precision' )
186 large = one / small
187*
188 IF( scond.GE.thresh .AND. amax.GE.small .AND. amax.LE.large ) THEN
189*
190* No equilibration
191*
192 equed = 'N'
193 ELSE
194*
195* Replace A by diag(S) * A * diag(S).
196*
197 IF( lsame( uplo, 'U' ) ) THEN
198*
199* Upper triangle of A is stored in band format.
200*
201 DO 20 j = 1, n
202 cj = s( j )
203 DO 10 i = max( 1, j-kd ), j - 1
204 ab( kd+1+i-j, j ) = cj*s( i )*ab( kd+1+i-j, j )
205 10 CONTINUE
206 ab( kd+1, j ) = cj*cj*real( ab( kd+1, j ) )
207 20 CONTINUE
208 ELSE
209*
210* Lower triangle of A is stored.
211*
212 DO 40 j = 1, n
213 cj = s( j )
214 ab( 1, j ) = cj*cj*real( ab( 1, j ) )
215 DO 30 i = j + 1, min( n, j+kd )
216 ab( 1+i-j, j ) = cj*s( i )*ab( 1+i-j, j )
217 30 CONTINUE
218 40 CONTINUE
219 END IF
220 equed = 'Y'
221 END IF
222*
223 RETURN
224*
225* End of CLAQHB
226*
227 END
subroutine claqhb(uplo, n, kd, ab, ldab, s, scond, amax, equed)
CLAQHB scales a Hermitian band matrix, using scaling factors computed by cpbequ.
Definition claqhb.f:141