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