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