LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlarrc.f
Go to the documentation of this file.
1*> \brief \b DLARRC computes the number of eigenvalues of the symmetric tridiagonal matrix.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DLARRC + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlarrc.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlarrc.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarrc.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DLARRC( JOBT, N, VL, VU, D, E, PIVMIN,
20* EIGCNT, LCNT, RCNT, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER JOBT
24* INTEGER EIGCNT, INFO, LCNT, N, RCNT
25* DOUBLE PRECISION PIVMIN, VL, VU
26* ..
27* .. Array Arguments ..
28* DOUBLE PRECISION D( * ), E( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> Find the number of eigenvalues of the symmetric tridiagonal matrix T
38*> that are in the interval (VL,VU] if JOBT = 'T', and of L D L^T
39*> if JOBT = 'L'.
40*> \endverbatim
41*
42* Arguments:
43* ==========
44*
45*> \param[in] JOBT
46*> \verbatim
47*> JOBT is CHARACTER*1
48*> = 'T': Compute Sturm count for matrix T.
49*> = 'L': Compute Sturm count for matrix L D L^T.
50*> \endverbatim
51*>
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The order of the matrix. N > 0.
56*> \endverbatim
57*>
58*> \param[in] VL
59*> \verbatim
60*> VL is DOUBLE PRECISION
61*> The lower bound for the eigenvalues.
62*> \endverbatim
63*>
64*> \param[in] VU
65*> \verbatim
66*> VU is DOUBLE PRECISION
67*> The upper bound for the eigenvalues.
68*> \endverbatim
69*>
70*> \param[in] D
71*> \verbatim
72*> D is DOUBLE PRECISION array, dimension (N)
73*> JOBT = 'T': The N diagonal elements of the tridiagonal matrix T.
74*> JOBT = 'L': The N diagonal elements of the diagonal matrix D.
75*> \endverbatim
76*>
77*> \param[in] E
78*> \verbatim
79*> E is DOUBLE PRECISION array, dimension (N)
80*> JOBT = 'T': The N-1 offdiagonal elements of the matrix T.
81*> JOBT = 'L': The N-1 offdiagonal elements of the matrix L.
82*> \endverbatim
83*>
84*> \param[in] PIVMIN
85*> \verbatim
86*> PIVMIN is DOUBLE PRECISION
87*> The minimum pivot in the Sturm sequence for T.
88*> \endverbatim
89*>
90*> \param[out] EIGCNT
91*> \verbatim
92*> EIGCNT is INTEGER
93*> The number of eigenvalues of the symmetric tridiagonal matrix T
94*> that are in the interval (VL,VU]
95*> \endverbatim
96*>
97*> \param[out] LCNT
98*> \verbatim
99*> LCNT is INTEGER
100*> \endverbatim
101*>
102*> \param[out] RCNT
103*> \verbatim
104*> RCNT is INTEGER
105*> The left and right negcounts of the interval.
106*> \endverbatim
107*>
108*> \param[out] INFO
109*> \verbatim
110*> INFO is INTEGER
111*> \endverbatim
112*
113* Authors:
114* ========
115*
116*> \author Univ. of Tennessee
117*> \author Univ. of California Berkeley
118*> \author Univ. of Colorado Denver
119*> \author NAG Ltd.
120*
121*> \ingroup larrc
122*
123*> \par Contributors:
124* ==================
125*>
126*> Beresford Parlett, University of California, Berkeley, USA \n
127*> Jim Demmel, University of California, Berkeley, USA \n
128*> Inderjit Dhillon, University of Texas, Austin, USA \n
129*> Osni Marques, LBNL/NERSC, USA \n
130*> Christof Voemel, University of California, Berkeley, USA
131*
132* =====================================================================
133 SUBROUTINE dlarrc( JOBT, N, VL, VU, D, E, PIVMIN,
134 $ EIGCNT, LCNT, RCNT, INFO )
135*
136* -- LAPACK auxiliary routine --
137* -- LAPACK is a software package provided by Univ. of Tennessee, --
138* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
139*
140* .. Scalar Arguments ..
141 CHARACTER JOBT
142 INTEGER EIGCNT, INFO, LCNT, N, RCNT
143 DOUBLE PRECISION PIVMIN, VL, VU
144* ..
145* .. Array Arguments ..
146 DOUBLE PRECISION D( * ), E( * )
147* ..
148*
149* =====================================================================
150*
151* .. Parameters ..
152 DOUBLE PRECISION ZERO
153 parameter( zero = 0.0d0 )
154* ..
155* .. Local Scalars ..
156 INTEGER I
157 LOGICAL MATT
158 DOUBLE PRECISION LPIVOT, RPIVOT, SL, SU, TMP, TMP2
159
160* ..
161* .. External Functions ..
162 LOGICAL LSAME
163 EXTERNAL lsame
164* ..
165* .. Executable Statements ..
166*
167 info = 0
168 lcnt = 0
169 rcnt = 0
170 eigcnt = 0
171*
172* Quick return if possible
173*
174 IF( n.LE.0 ) THEN
175 RETURN
176 END IF
177*
178 matt = lsame( jobt, 'T' )
179
180
181 IF (matt) THEN
182* Sturm sequence count on T
183 lpivot = d( 1 ) - vl
184 rpivot = d( 1 ) - vu
185 IF( lpivot.LE.zero ) THEN
186 lcnt = lcnt + 1
187 ENDIF
188 IF( rpivot.LE.zero ) THEN
189 rcnt = rcnt + 1
190 ENDIF
191 DO 10 i = 1, n-1
192 tmp = e(i)**2
193 lpivot = ( d( i+1 )-vl ) - tmp/lpivot
194 rpivot = ( d( i+1 )-vu ) - tmp/rpivot
195 IF( lpivot.LE.zero ) THEN
196 lcnt = lcnt + 1
197 ENDIF
198 IF( rpivot.LE.zero ) THEN
199 rcnt = rcnt + 1
200 ENDIF
201 10 CONTINUE
202 ELSE
203* Sturm sequence count on L D L^T
204 sl = -vl
205 su = -vu
206 DO 20 i = 1, n - 1
207 lpivot = d( i ) + sl
208 rpivot = d( i ) + su
209 IF( lpivot.LE.zero ) THEN
210 lcnt = lcnt + 1
211 ENDIF
212 IF( rpivot.LE.zero ) THEN
213 rcnt = rcnt + 1
214 ENDIF
215 tmp = e(i) * d(i) * e(i)
216*
217 tmp2 = tmp / lpivot
218 IF( tmp2.EQ.zero ) THEN
219 sl = tmp - vl
220 ELSE
221 sl = sl*tmp2 - vl
222 END IF
223*
224 tmp2 = tmp / rpivot
225 IF( tmp2.EQ.zero ) THEN
226 su = tmp - vu
227 ELSE
228 su = su*tmp2 - vu
229 END IF
230 20 CONTINUE
231 lpivot = d( n ) + sl
232 rpivot = d( n ) + su
233 IF( lpivot.LE.zero ) THEN
234 lcnt = lcnt + 1
235 ENDIF
236 IF( rpivot.LE.zero ) THEN
237 rcnt = rcnt + 1
238 ENDIF
239 ENDIF
240 eigcnt = rcnt - lcnt
241
242 RETURN
243*
244* End of DLARRC
245*
246 END
subroutine dlarrc(jobt, n, vl, vu, d, e, pivmin, eigcnt, lcnt, rcnt, info)
DLARRC computes the number of eigenvalues of the symmetric tridiagonal matrix.
Definition dlarrc.f:135