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