1 *> \brief \b SLARRJ performs refinement of the initial estimates of the eigenvalues of the matrix T.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SLARRJ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slarrj.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slarrj.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slarrj.f">
21 * SUBROUTINE SLARRJ( N, D, E2, IFIRST, ILAST,
22 * RTOL, OFFSET, W, WERR, WORK, IWORK,
23 * PIVMIN, SPDIAM, INFO )
25 * .. Scalar Arguments ..
26 * INTEGER IFIRST, ILAST, INFO, N, OFFSET
27 * REAL PIVMIN, RTOL, SPDIAM
29 * .. Array Arguments ..
31 * REAL D( * ), E2( * ), W( * ),
32 * $ WERR( * ), WORK( * )
41 *> Given the initial eigenvalue approximations of T, SLARRJ
42 *> does bisection to refine the eigenvalues of T,
43 *> W( IFIRST-OFFSET ) through W( ILAST-OFFSET ), to more accuracy. Initial
44 *> guesses for these eigenvalues are input in W, the corresponding estimate
45 *> of the error in these guesses in WERR. During bisection, intervals
46 *> [left, right] are maintained by storing their mid-points and
47 *> semi-widths in the arrays W and WERR respectively.
56 *> The order of the matrix.
61 *> D is REAL array, dimension (N)
62 *> The N diagonal elements of T.
67 *> E2 is REAL array, dimension (N-1)
68 *> The Squares of the (N-1) subdiagonal elements of T.
74 *> The index of the first eigenvalue to be computed.
80 *> The index of the last eigenvalue to be computed.
86 *> Tolerance for the convergence of the bisection intervals.
87 *> An interval [LEFT,RIGHT] has converged if
88 *> RIGHT-LEFT.LT.RTOL*MAX(|LEFT|,|RIGHT|).
94 *> Offset for the arrays W and WERR, i.e., the IFIRST-OFFSET
95 *> through ILAST-OFFSET elements of these arrays are to be used.
100 *> W is REAL array, dimension (N)
101 *> On input, W( IFIRST-OFFSET ) through W( ILAST-OFFSET ) are
102 *> estimates of the eigenvalues of L D L^T indexed IFIRST through
104 *> On output, these estimates are refined.
107 *> \param[in,out] WERR
109 *> WERR is REAL array, dimension (N)
110 *> On input, WERR( IFIRST-OFFSET ) through WERR( ILAST-OFFSET ) are
111 *> the errors in the estimates of the corresponding elements in W.
112 *> On output, these errors are refined.
117 *> WORK is REAL array, dimension (2*N)
123 *> IWORK is INTEGER array, dimension (2*N)
130 *> The minimum pivot in the Sturm sequence for T.
136 *> The spectral diameter of T.
148 *> \author Univ. of Tennessee
149 *> \author Univ. of California Berkeley
150 *> \author Univ. of Colorado Denver
153 *> \date September 2012
155 *> \ingroup auxOTHERauxiliary
157 *> \par Contributors:
160 *> Beresford Parlett, University of California, Berkeley, USA \n
161 *> Jim Demmel, University of California, Berkeley, USA \n
162 *> Inderjit Dhillon, University of Texas, Austin, USA \n
163 *> Osni Marques, LBNL/NERSC, USA \n
164 *> Christof Voemel, University of California, Berkeley, USA
166 * =====================================================================
167 SUBROUTINE SLARRJ( N, D, E2, IFIRST, ILAST,
168 $ RTOL, OFFSET, W, WERR, WORK, IWORK,
169 $ PIVMIN, SPDIAM, INFO )
171 * -- LAPACK auxiliary routine (version 3.4.2) --
172 * -- LAPACK is a software package provided by Univ. of Tennessee, --
173 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
176 * .. Scalar Arguments ..
177 INTEGER IFIRST, ILAST, INFO, N, OFFSET
178 REAL PIVMIN, RTOL, SPDIAM
180 * .. Array Arguments ..
182 REAL D( * ), E2( * ), W( * ),
183 $ WERR( * ), WORK( * )
186 * =====================================================================
189 REAL ZERO, ONE, TWO, HALF
190 PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0, TWO = 2.0E0,
194 * .. Local Scalars ..
195 INTEGER CNT, I, I1, I2, II, ITER, J, K, NEXT, NINT,
196 $ OLNINT, P, PREV, SAVI1
197 REAL DPLUS, FAC, LEFT, MID, RIGHT, S, TMP, WIDTH
200 * .. Intrinsic Functions ..
203 * .. Executable Statements ..
207 MAXITR = INT( ( LOG( SPDIAM+PIVMIN )-LOG( PIVMIN ) ) /
210 * Initialize unconverged intervals in [ WORK(2*I-1), WORK(2*I) ].
211 * The Sturm Count, Count( WORK(2*I-1) ) is arranged to be I-1, while
212 * Count( WORK(2*I) ) is stored in IWORK( 2*I ). The integer IWORK( 2*I-1 )
213 * for an unconverged interval is set to the index of the next unconverged
214 * interval, and is -1 or 0 for a converged interval. Thus a linked
215 * list of unconverged intervals is set up.
220 * The number of unconverged intervals
222 * The last unconverged interval found
227 LEFT = W( II ) - WERR( II )
229 RIGHT = W( II ) + WERR( II )
231 TMP = MAX( ABS( LEFT ), ABS( RIGHT ) )
233 * The following test prevents the test of converged intervals
234 IF( WIDTH.LT.RTOL*TMP ) THEN
235 * This interval has already converged and does not need refinement.
236 * (Note that the gaps might change through refining the
237 * eigenvalues, however, they can only get bigger.)
238 * Remove it from the list.
240 * Make sure that I1 always points to the first unconverged interval
241 IF((I.EQ.I1).AND.(I.LT.I2)) I1 = I + 1
242 IF((PREV.GE.I1).AND.(I.LE.I2)) IWORK( 2*PREV-1 ) = I + 1
244 * unconverged interval found
246 * Make sure that [LEFT,RIGHT] contains the desired eigenvalue
248 * Do while( CNT(LEFT).GT.I-1 )
255 IF( DPLUS.LT.ZERO ) CNT = CNT + 1
257 DPLUS = D( J ) - S - E2( J-1 )/DPLUS
258 IF( DPLUS.LT.ZERO ) CNT = CNT + 1
260 IF( CNT.GT.I-1 ) THEN
261 LEFT = LEFT - WERR( II )*FAC
266 * Do while( CNT(RIGHT).LT.I )
273 IF( DPLUS.LT.ZERO ) CNT = CNT + 1
275 DPLUS = D( J ) - S - E2( J-1 )/DPLUS
276 IF( DPLUS.LT.ZERO ) CNT = CNT + 1
279 RIGHT = RIGHT + WERR( II )*FAC
294 * Do while( NINT.GT.0 ), i.e. there are still unconverged intervals
295 * and while (ITER.LT.MAXITR)
309 MID = HALF*( LEFT + RIGHT )
311 * semiwidth of interval
313 TMP = MAX( ABS( LEFT ), ABS( RIGHT ) )
315 IF( ( WIDTH.LT.RTOL*TMP ) .OR.
316 $ (ITER.EQ.MAXITR) )THEN
317 * reduce number of unconverged intervals
319 * Mark interval as converged.
324 * Prev holds the last unconverged interval previously examined
325 IF(PREV.GE.I1) IWORK( 2*PREV-1 ) = NEXT
332 * Perform one bisection step
337 IF( DPLUS.LT.ZERO ) CNT = CNT + 1
339 DPLUS = D( J ) - S - E2( J-1 )/DPLUS
340 IF( DPLUS.LT.ZERO ) CNT = CNT + 1
342 IF( CNT.LE.I-1 ) THEN
351 * do another loop if there are still unconverged intervals
352 * However, in the last iteration, all intervals are accepted
353 * since this is the best we can do.
354 IF( ( NINT.GT.0 ).AND.(ITER.LE.MAXITR) ) GO TO 80
357 * At this point, all the intervals have converged
358 DO 110 I = SAVI1, ILAST
361 * All intervals marked by '0' have been refined.
362 IF( IWORK( K-1 ).EQ.0 ) THEN
363 W( II ) = HALF*( WORK( K-1 )+WORK( K ) )
364 WERR( II ) = WORK( K ) - W( II )