LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
sstebz.f
Go to the documentation of this file.
1 *> \brief \b SSTEBZ
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SSTEBZ + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sstebz.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sstebz.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sstebz.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SSTEBZ( RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E,
22 * M, NSPLIT, W, IBLOCK, ISPLIT, WORK, IWORK,
23 * INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER ORDER, RANGE
27 * INTEGER IL, INFO, IU, M, N, NSPLIT
28 * REAL ABSTOL, VL, VU
29 * ..
30 * .. Array Arguments ..
31 * INTEGER IBLOCK( * ), ISPLIT( * ), IWORK( * )
32 * REAL D( * ), E( * ), W( * ), WORK( * )
33 * ..
34 *
35 *
36 *> \par Purpose:
37 * =============
38 *>
39 *> \verbatim
40 *>
41 *> SSTEBZ computes the eigenvalues of a symmetric tridiagonal
42 *> matrix T. The user may ask for all eigenvalues, all eigenvalues
43 *> in the half-open interval (VL, VU], or the IL-th through IU-th
44 *> eigenvalues.
45 *>
46 *> To avoid overflow, the matrix must be scaled so that its
47 *> largest element is no greater than overflow**(1/2) * underflow**(1/4) in absolute value, and for greatest
48 *> accuracy, it should not be much smaller than that.
49 *>
50 *> See W. Kahan "Accurate Eigenvalues of a Symmetric Tridiagonal
51 *> Matrix", Report CS41, Computer Science Dept., Stanford
52 *> University, July 21, 1966.
53 *> \endverbatim
54 *
55 * Arguments:
56 * ==========
57 *
58 *> \param[in] RANGE
59 *> \verbatim
60 *> RANGE is CHARACTER*1
61 *> = 'A': ("All") all eigenvalues will be found.
62 *> = 'V': ("Value") all eigenvalues in the half-open interval
63 *> (VL, VU] will be found.
64 *> = 'I': ("Index") the IL-th through IU-th eigenvalues (of the
65 *> entire matrix) will be found.
66 *> \endverbatim
67 *>
68 *> \param[in] ORDER
69 *> \verbatim
70 *> ORDER is CHARACTER*1
71 *> = 'B': ("By Block") the eigenvalues will be grouped by
72 *> split-off block (see IBLOCK, ISPLIT) and
73 *> ordered from smallest to largest within
74 *> the block.
75 *> = 'E': ("Entire matrix")
76 *> the eigenvalues for the entire matrix
77 *> will be ordered from smallest to
78 *> largest.
79 *> \endverbatim
80 *>
81 *> \param[in] N
82 *> \verbatim
83 *> N is INTEGER
84 *> The order of the tridiagonal matrix T. N >= 0.
85 *> \endverbatim
86 *>
87 *> \param[in] VL
88 *> \verbatim
89 *> VL is REAL
90 *> \endverbatim
91 *>
92 *> \param[in] VU
93 *> \verbatim
94 *> VU is REAL
95 *>
96 *> If RANGE='V', the lower and upper bounds of the interval to
97 *> be searched for eigenvalues. Eigenvalues less than or equal
98 *> to VL, or greater than VU, will not be returned. VL < VU.
99 *> Not referenced if RANGE = 'A' or 'I'.
100 *> \endverbatim
101 *>
102 *> \param[in] IL
103 *> \verbatim
104 *> IL is INTEGER
105 *> \endverbatim
106 *>
107 *> \param[in] IU
108 *> \verbatim
109 *> IU is INTEGER
110 *>
111 *> If RANGE='I', the indices (in ascending order) of the
112 *> smallest and largest eigenvalues to be returned.
113 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
114 *> Not referenced if RANGE = 'A' or 'V'.
115 *> \endverbatim
116 *>
117 *> \param[in] ABSTOL
118 *> \verbatim
119 *> ABSTOL is REAL
120 *> The absolute tolerance for the eigenvalues. An eigenvalue
121 *> (or cluster) is considered to be located if it has been
122 *> determined to lie in an interval whose width is ABSTOL or
123 *> less. If ABSTOL is less than or equal to zero, then ULP*|T|
124 *> will be used, where |T| means the 1-norm of T.
125 *>
126 *> Eigenvalues will be computed most accurately when ABSTOL is
127 *> set to twice the underflow threshold 2*SLAMCH('S'), not zero.
128 *> \endverbatim
129 *>
130 *> \param[in] D
131 *> \verbatim
132 *> D is REAL array, dimension (N)
133 *> The n diagonal elements of the tridiagonal matrix T.
134 *> \endverbatim
135 *>
136 *> \param[in] E
137 *> \verbatim
138 *> E is REAL array, dimension (N-1)
139 *> The (n-1) off-diagonal elements of the tridiagonal matrix T.
140 *> \endverbatim
141 *>
142 *> \param[out] M
143 *> \verbatim
144 *> M is INTEGER
145 *> The actual number of eigenvalues found. 0 <= M <= N.
146 *> (See also the description of INFO=2,3.)
147 *> \endverbatim
148 *>
149 *> \param[out] NSPLIT
150 *> \verbatim
151 *> NSPLIT is INTEGER
152 *> The number of diagonal blocks in the matrix T.
153 *> 1 <= NSPLIT <= N.
154 *> \endverbatim
155 *>
156 *> \param[out] W
157 *> \verbatim
158 *> W is REAL array, dimension (N)
159 *> On exit, the first M elements of W will contain the
160 *> eigenvalues. (SSTEBZ may use the remaining N-M elements as
161 *> workspace.)
162 *> \endverbatim
163 *>
164 *> \param[out] IBLOCK
165 *> \verbatim
166 *> IBLOCK is INTEGER array, dimension (N)
167 *> At each row/column j where E(j) is zero or small, the
168 *> matrix T is considered to split into a block diagonal
169 *> matrix. On exit, if INFO = 0, IBLOCK(i) specifies to which
170 *> block (from 1 to the number of blocks) the eigenvalue W(i)
171 *> belongs. (SSTEBZ may use the remaining N-M elements as
172 *> workspace.)
173 *> \endverbatim
174 *>
175 *> \param[out] ISPLIT
176 *> \verbatim
177 *> ISPLIT is INTEGER array, dimension (N)
178 *> The splitting points, at which T breaks up into submatrices.
179 *> The first submatrix consists of rows/columns 1 to ISPLIT(1),
180 *> the second of rows/columns ISPLIT(1)+1 through ISPLIT(2),
181 *> etc., and the NSPLIT-th consists of rows/columns
182 *> ISPLIT(NSPLIT-1)+1 through ISPLIT(NSPLIT)=N.
183 *> (Only the first NSPLIT elements will actually be used, but
184 *> since the user cannot know a priori what value NSPLIT will
185 *> have, N words must be reserved for ISPLIT.)
186 *> \endverbatim
187 *>
188 *> \param[out] WORK
189 *> \verbatim
190 *> WORK is REAL array, dimension (4*N)
191 *> \endverbatim
192 *>
193 *> \param[out] IWORK
194 *> \verbatim
195 *> IWORK is INTEGER array, dimension (3*N)
196 *> \endverbatim
197 *>
198 *> \param[out] INFO
199 *> \verbatim
200 *> INFO is INTEGER
201 *> = 0: successful exit
202 *> < 0: if INFO = -i, the i-th argument had an illegal value
203 *> > 0: some or all of the eigenvalues failed to converge or
204 *> were not computed:
205 *> =1 or 3: Bisection failed to converge for some
206 *> eigenvalues; these eigenvalues are flagged by a
207 *> negative block number. The effect is that the
208 *> eigenvalues may not be as accurate as the
209 *> absolute and relative tolerances. This is
210 *> generally caused by unexpectedly inaccurate
211 *> arithmetic.
212 *> =2 or 3: RANGE='I' only: Not all of the eigenvalues
213 *> IL:IU were found.
214 *> Effect: M < IU+1-IL
215 *> Cause: non-monotonic arithmetic, causing the
216 *> Sturm sequence to be non-monotonic.
217 *> Cure: recalculate, using RANGE='A', and pick
218 *> out eigenvalues IL:IU. In some cases,
219 *> increasing the PARAMETER "FUDGE" may
220 *> make things work.
221 *> = 4: RANGE='I', and the Gershgorin interval
222 *> initially used was too small. No eigenvalues
223 *> were computed.
224 *> Probable cause: your machine has sloppy
225 *> floating-point arithmetic.
226 *> Cure: Increase the PARAMETER "FUDGE",
227 *> recompile, and try again.
228 *> \endverbatim
229 *
230 *> \par Internal Parameters:
231 * =========================
232 *>
233 *> \verbatim
234 *> RELFAC REAL, default = 2.0e0
235 *> The relative tolerance. An interval (a,b] lies within
236 *> "relative tolerance" if b-a < RELFAC*ulp*max(|a|,|b|),
237 *> where "ulp" is the machine precision (distance from 1 to
238 *> the next larger floating point number.)
239 *>
240 *> FUDGE REAL, default = 2
241 *> A "fudge factor" to widen the Gershgorin intervals. Ideally,
242 *> a value of 1 should work, but on machines with sloppy
243 *> arithmetic, this needs to be larger. The default for
244 *> publicly released versions should be large enough to handle
245 *> the worst machine around. Note that this has no effect
246 *> on accuracy of the solution.
247 *> \endverbatim
248 *
249 * Authors:
250 * ========
251 *
252 *> \author Univ. of Tennessee
253 *> \author Univ. of California Berkeley
254 *> \author Univ. of Colorado Denver
255 *> \author NAG Ltd.
256 *
257 *> \date November 2011
258 *
259 *> \ingroup auxOTHERcomputational
260 *
261 * =====================================================================
262  SUBROUTINE sstebz( RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E,
263  $ m, nsplit, w, iblock, isplit, work, iwork,
264  $ info )
265 *
266 * -- LAPACK computational routine (version 3.4.0) --
267 * -- LAPACK is a software package provided by Univ. of Tennessee, --
268 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
269 * November 2011
270 *
271 * .. Scalar Arguments ..
272  CHARACTER order, range
273  INTEGER il, info, iu, m, n, nsplit
274  REAL abstol, vl, vu
275 * ..
276 * .. Array Arguments ..
277  INTEGER iblock( * ), isplit( * ), iwork( * )
278  REAL d( * ), e( * ), w( * ), work( * )
279 * ..
280 *
281 * =====================================================================
282 *
283 * .. Parameters ..
284  REAL zero, one, two, half
285  parameter( zero = 0.0e0, one = 1.0e0, two = 2.0e0,
286  $ half = 1.0e0 / two )
287  REAL fudge, relfac
288  parameter( fudge = 2.1e0, relfac = 2.0e0 )
289 * ..
290 * .. Local Scalars ..
291  LOGICAL ncnvrg, toofew
292  INTEGER ib, ibegin, idiscl, idiscu, ie, iend, iinfo,
293  $ im, in, ioff, iorder, iout, irange, itmax,
294  $ itmp1, iw, iwoff, j, jb, jdisc, je, nb, nwl,
295  $ nwu
296  REAL atoli, bnorm, gl, gu, pivmin, rtoli, safemn,
297  $ tmp1, tmp2, tnorm, ulp, wkill, wl, wlu, wu, wul
298 * ..
299 * .. Local Arrays ..
300  INTEGER idumma( 1 )
301 * ..
302 * .. External Functions ..
303  LOGICAL lsame
304  INTEGER ilaenv
305  REAL slamch
306  EXTERNAL lsame, ilaenv, slamch
307 * ..
308 * .. External Subroutines ..
309  EXTERNAL slaebz, xerbla
310 * ..
311 * .. Intrinsic Functions ..
312  INTRINSIC abs, int, log, max, min, sqrt
313 * ..
314 * .. Executable Statements ..
315 *
316  info = 0
317 *
318 * Decode RANGE
319 *
320  IF( lsame( range, 'A' ) ) THEN
321  irange = 1
322  ELSE IF( lsame( range, 'V' ) ) THEN
323  irange = 2
324  ELSE IF( lsame( range, 'I' ) ) THEN
325  irange = 3
326  ELSE
327  irange = 0
328  END IF
329 *
330 * Decode ORDER
331 *
332  IF( lsame( order, 'B' ) ) THEN
333  iorder = 2
334  ELSE IF( lsame( order, 'E' ) ) THEN
335  iorder = 1
336  ELSE
337  iorder = 0
338  END IF
339 *
340 * Check for Errors
341 *
342  IF( irange.LE.0 ) THEN
343  info = -1
344  ELSE IF( iorder.LE.0 ) THEN
345  info = -2
346  ELSE IF( n.LT.0 ) THEN
347  info = -3
348  ELSE IF( irange.EQ.2 ) THEN
349  IF( vl.GE.vu ) info = -5
350  ELSE IF( irange.EQ.3 .AND. ( il.LT.1 .OR. il.GT.max( 1, n ) ) )
351  $ THEN
352  info = -6
353  ELSE IF( irange.EQ.3 .AND. ( iu.LT.min( n, il ) .OR. iu.GT.n ) )
354  $ THEN
355  info = -7
356  END IF
357 *
358  IF( info.NE.0 ) THEN
359  CALL xerbla( 'SSTEBZ', -info )
360  return
361  END IF
362 *
363 * Initialize error flags
364 *
365  info = 0
366  ncnvrg = .false.
367  toofew = .false.
368 *
369 * Quick return if possible
370 *
371  m = 0
372  IF( n.EQ.0 )
373  $ return
374 *
375 * Simplifications:
376 *
377  IF( irange.EQ.3 .AND. il.EQ.1 .AND. iu.EQ.n )
378  $ irange = 1
379 *
380 * Get machine constants
381 * NB is the minimum vector length for vector bisection, or 0
382 * if only scalar is to be done.
383 *
384  safemn = slamch( 'S' )
385  ulp = slamch( 'P' )
386  rtoli = ulp*relfac
387  nb = ilaenv( 1, 'SSTEBZ', ' ', n, -1, -1, -1 )
388  IF( nb.LE.1 )
389  $ nb = 0
390 *
391 * Special Case when N=1
392 *
393  IF( n.EQ.1 ) THEN
394  nsplit = 1
395  isplit( 1 ) = 1
396  IF( irange.EQ.2 .AND. ( vl.GE.d( 1 ) .OR. vu.LT.d( 1 ) ) ) THEN
397  m = 0
398  ELSE
399  w( 1 ) = d( 1 )
400  iblock( 1 ) = 1
401  m = 1
402  END IF
403  return
404  END IF
405 *
406 * Compute Splitting Points
407 *
408  nsplit = 1
409  work( n ) = zero
410  pivmin = one
411 *
412  DO 10 j = 2, n
413  tmp1 = e( j-1 )**2
414  IF( abs( d( j )*d( j-1 ) )*ulp**2+safemn.GT.tmp1 ) THEN
415  isplit( nsplit ) = j - 1
416  nsplit = nsplit + 1
417  work( j-1 ) = zero
418  ELSE
419  work( j-1 ) = tmp1
420  pivmin = max( pivmin, tmp1 )
421  END IF
422  10 continue
423  isplit( nsplit ) = n
424  pivmin = pivmin*safemn
425 *
426 * Compute Interval and ATOLI
427 *
428  IF( irange.EQ.3 ) THEN
429 *
430 * RANGE='I': Compute the interval containing eigenvalues
431 * IL through IU.
432 *
433 * Compute Gershgorin interval for entire (split) matrix
434 * and use it as the initial interval
435 *
436  gu = d( 1 )
437  gl = d( 1 )
438  tmp1 = zero
439 *
440  DO 20 j = 1, n - 1
441  tmp2 = sqrt( work( j ) )
442  gu = max( gu, d( j )+tmp1+tmp2 )
443  gl = min( gl, d( j )-tmp1-tmp2 )
444  tmp1 = tmp2
445  20 continue
446 *
447  gu = max( gu, d( n )+tmp1 )
448  gl = min( gl, d( n )-tmp1 )
449  tnorm = max( abs( gl ), abs( gu ) )
450  gl = gl - fudge*tnorm*ulp*n - fudge*two*pivmin
451  gu = gu + fudge*tnorm*ulp*n + fudge*pivmin
452 *
453 * Compute Iteration parameters
454 *
455  itmax = int( ( log( tnorm+pivmin )-log( pivmin ) ) /
456  $ log( two ) ) + 2
457  IF( abstol.LE.zero ) THEN
458  atoli = ulp*tnorm
459  ELSE
460  atoli = abstol
461  END IF
462 *
463  work( n+1 ) = gl
464  work( n+2 ) = gl
465  work( n+3 ) = gu
466  work( n+4 ) = gu
467  work( n+5 ) = gl
468  work( n+6 ) = gu
469  iwork( 1 ) = -1
470  iwork( 2 ) = -1
471  iwork( 3 ) = n + 1
472  iwork( 4 ) = n + 1
473  iwork( 5 ) = il - 1
474  iwork( 6 ) = iu
475 *
476  CALL slaebz( 3, itmax, n, 2, 2, nb, atoli, rtoli, pivmin, d, e,
477  $ work, iwork( 5 ), work( n+1 ), work( n+5 ), iout,
478  $ iwork, w, iblock, iinfo )
479 *
480  IF( iwork( 6 ).EQ.iu ) THEN
481  wl = work( n+1 )
482  wlu = work( n+3 )
483  nwl = iwork( 1 )
484  wu = work( n+4 )
485  wul = work( n+2 )
486  nwu = iwork( 4 )
487  ELSE
488  wl = work( n+2 )
489  wlu = work( n+4 )
490  nwl = iwork( 2 )
491  wu = work( n+3 )
492  wul = work( n+1 )
493  nwu = iwork( 3 )
494  END IF
495 *
496  IF( nwl.LT.0 .OR. nwl.GE.n .OR. nwu.LT.1 .OR. nwu.GT.n ) THEN
497  info = 4
498  return
499  END IF
500  ELSE
501 *
502 * RANGE='A' or 'V' -- Set ATOLI
503 *
504  tnorm = max( abs( d( 1 ) )+abs( e( 1 ) ),
505  $ abs( d( n ) )+abs( e( n-1 ) ) )
506 *
507  DO 30 j = 2, n - 1
508  tnorm = max( tnorm, abs( d( j ) )+abs( e( j-1 ) )+
509  $ abs( e( j ) ) )
510  30 continue
511 *
512  IF( abstol.LE.zero ) THEN
513  atoli = ulp*tnorm
514  ELSE
515  atoli = abstol
516  END IF
517 *
518  IF( irange.EQ.2 ) THEN
519  wl = vl
520  wu = vu
521  ELSE
522  wl = zero
523  wu = zero
524  END IF
525  END IF
526 *
527 * Find Eigenvalues -- Loop Over Blocks and recompute NWL and NWU.
528 * NWL accumulates the number of eigenvalues .le. WL,
529 * NWU accumulates the number of eigenvalues .le. WU
530 *
531  m = 0
532  iend = 0
533  info = 0
534  nwl = 0
535  nwu = 0
536 *
537  DO 70 jb = 1, nsplit
538  ioff = iend
539  ibegin = ioff + 1
540  iend = isplit( jb )
541  in = iend - ioff
542 *
543  IF( in.EQ.1 ) THEN
544 *
545 * Special Case -- IN=1
546 *
547  IF( irange.EQ.1 .OR. wl.GE.d( ibegin )-pivmin )
548  $ nwl = nwl + 1
549  IF( irange.EQ.1 .OR. wu.GE.d( ibegin )-pivmin )
550  $ nwu = nwu + 1
551  IF( irange.EQ.1 .OR. ( wl.LT.d( ibegin )-pivmin .AND. wu.GE.
552  $ d( ibegin )-pivmin ) ) THEN
553  m = m + 1
554  w( m ) = d( ibegin )
555  iblock( m ) = jb
556  END IF
557  ELSE
558 *
559 * General Case -- IN > 1
560 *
561 * Compute Gershgorin Interval
562 * and use it as the initial interval
563 *
564  gu = d( ibegin )
565  gl = d( ibegin )
566  tmp1 = zero
567 *
568  DO 40 j = ibegin, iend - 1
569  tmp2 = abs( e( j ) )
570  gu = max( gu, d( j )+tmp1+tmp2 )
571  gl = min( gl, d( j )-tmp1-tmp2 )
572  tmp1 = tmp2
573  40 continue
574 *
575  gu = max( gu, d( iend )+tmp1 )
576  gl = min( gl, d( iend )-tmp1 )
577  bnorm = max( abs( gl ), abs( gu ) )
578  gl = gl - fudge*bnorm*ulp*in - fudge*pivmin
579  gu = gu + fudge*bnorm*ulp*in + fudge*pivmin
580 *
581 * Compute ATOLI for the current submatrix
582 *
583  IF( abstol.LE.zero ) THEN
584  atoli = ulp*max( abs( gl ), abs( gu ) )
585  ELSE
586  atoli = abstol
587  END IF
588 *
589  IF( irange.GT.1 ) THEN
590  IF( gu.LT.wl ) THEN
591  nwl = nwl + in
592  nwu = nwu + in
593  go to 70
594  END IF
595  gl = max( gl, wl )
596  gu = min( gu, wu )
597  IF( gl.GE.gu )
598  $ go to 70
599  END IF
600 *
601 * Set Up Initial Interval
602 *
603  work( n+1 ) = gl
604  work( n+in+1 ) = gu
605  CALL slaebz( 1, 0, in, in, 1, nb, atoli, rtoli, pivmin,
606  $ d( ibegin ), e( ibegin ), work( ibegin ),
607  $ idumma, work( n+1 ), work( n+2*in+1 ), im,
608  $ iwork, w( m+1 ), iblock( m+1 ), iinfo )
609 *
610  nwl = nwl + iwork( 1 )
611  nwu = nwu + iwork( in+1 )
612  iwoff = m - iwork( 1 )
613 *
614 * Compute Eigenvalues
615 *
616  itmax = int( ( log( gu-gl+pivmin )-log( pivmin ) ) /
617  $ log( two ) ) + 2
618  CALL slaebz( 2, itmax, in, in, 1, nb, atoli, rtoli, pivmin,
619  $ d( ibegin ), e( ibegin ), work( ibegin ),
620  $ idumma, work( n+1 ), work( n+2*in+1 ), iout,
621  $ iwork, w( m+1 ), iblock( m+1 ), iinfo )
622 *
623 * Copy Eigenvalues Into W and IBLOCK
624 * Use -JB for block number for unconverged eigenvalues.
625 *
626  DO 60 j = 1, iout
627  tmp1 = half*( work( j+n )+work( j+in+n ) )
628 *
629 * Flag non-convergence.
630 *
631  IF( j.GT.iout-iinfo ) THEN
632  ncnvrg = .true.
633  ib = -jb
634  ELSE
635  ib = jb
636  END IF
637  DO 50 je = iwork( j ) + 1 + iwoff,
638  $ iwork( j+in ) + iwoff
639  w( je ) = tmp1
640  iblock( je ) = ib
641  50 continue
642  60 continue
643 *
644  m = m + im
645  END IF
646  70 continue
647 *
648 * If RANGE='I', then (WL,WU) contains eigenvalues NWL+1,...,NWU
649 * If NWL+1 < IL or NWU > IU, discard extra eigenvalues.
650 *
651  IF( irange.EQ.3 ) THEN
652  im = 0
653  idiscl = il - 1 - nwl
654  idiscu = nwu - iu
655 *
656  IF( idiscl.GT.0 .OR. idiscu.GT.0 ) THEN
657  DO 80 je = 1, m
658  IF( w( je ).LE.wlu .AND. idiscl.GT.0 ) THEN
659  idiscl = idiscl - 1
660  ELSE IF( w( je ).GE.wul .AND. idiscu.GT.0 ) THEN
661  idiscu = idiscu - 1
662  ELSE
663  im = im + 1
664  w( im ) = w( je )
665  iblock( im ) = iblock( je )
666  END IF
667  80 continue
668  m = im
669  END IF
670  IF( idiscl.GT.0 .OR. idiscu.GT.0 ) THEN
671 *
672 * Code to deal with effects of bad arithmetic:
673 * Some low eigenvalues to be discarded are not in (WL,WLU],
674 * or high eigenvalues to be discarded are not in (WUL,WU]
675 * so just kill off the smallest IDISCL/largest IDISCU
676 * eigenvalues, by simply finding the smallest/largest
677 * eigenvalue(s).
678 *
679 * (If N(w) is monotone non-decreasing, this should never
680 * happen.)
681 *
682  IF( idiscl.GT.0 ) THEN
683  wkill = wu
684  DO 100 jdisc = 1, idiscl
685  iw = 0
686  DO 90 je = 1, m
687  IF( iblock( je ).NE.0 .AND.
688  $ ( w( je ).LT.wkill .OR. iw.EQ.0 ) ) THEN
689  iw = je
690  wkill = w( je )
691  END IF
692  90 continue
693  iblock( iw ) = 0
694  100 continue
695  END IF
696  IF( idiscu.GT.0 ) THEN
697 *
698  wkill = wl
699  DO 120 jdisc = 1, idiscu
700  iw = 0
701  DO 110 je = 1, m
702  IF( iblock( je ).NE.0 .AND.
703  $ ( w( je ).GT.wkill .OR. iw.EQ.0 ) ) THEN
704  iw = je
705  wkill = w( je )
706  END IF
707  110 continue
708  iblock( iw ) = 0
709  120 continue
710  END IF
711  im = 0
712  DO 130 je = 1, m
713  IF( iblock( je ).NE.0 ) THEN
714  im = im + 1
715  w( im ) = w( je )
716  iblock( im ) = iblock( je )
717  END IF
718  130 continue
719  m = im
720  END IF
721  IF( idiscl.LT.0 .OR. idiscu.LT.0 ) THEN
722  toofew = .true.
723  END IF
724  END IF
725 *
726 * If ORDER='B', do nothing -- the eigenvalues are already sorted
727 * by block.
728 * If ORDER='E', sort the eigenvalues from smallest to largest
729 *
730  IF( iorder.EQ.1 .AND. nsplit.GT.1 ) THEN
731  DO 150 je = 1, m - 1
732  ie = 0
733  tmp1 = w( je )
734  DO 140 j = je + 1, m
735  IF( w( j ).LT.tmp1 ) THEN
736  ie = j
737  tmp1 = w( j )
738  END IF
739  140 continue
740 *
741  IF( ie.NE.0 ) THEN
742  itmp1 = iblock( ie )
743  w( ie ) = w( je )
744  iblock( ie ) = iblock( je )
745  w( je ) = tmp1
746  iblock( je ) = itmp1
747  END IF
748  150 continue
749  END IF
750 *
751  info = 0
752  IF( ncnvrg )
753  $ info = info + 1
754  IF( toofew )
755  $ info = info + 2
756  return
757 *
758 * End of SSTEBZ
759 *
760  END