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