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