1DSTEBZ(1)                LAPACK routine (version 3.1)                DSTEBZ(1)
2
3
4

NAME

6       DSTEBZ - the eigenvalues of a symmetric tridiagonal matrix T
7

SYNOPSIS

9       SUBROUTINE DSTEBZ( RANGE,  ORDER,  N,  VL, VU, IL, IU, ABSTOL, D, E, M,
10                          NSPLIT, W, IBLOCK, ISPLIT, WORK, IWORK, INFO )
11
12           CHARACTER      ORDER, RANGE
13
14           INTEGER        IL, INFO, IU, M, N, NSPLIT
15
16           DOUBLE         PRECISION ABSTOL, VL, VU
17
18           INTEGER        IBLOCK( * ), ISPLIT( * ), IWORK( * )
19
20           DOUBLE         PRECISION D( * ), E( * ), W( * ), WORK( * )
21

PURPOSE

23       DSTEBZ computes the eigenvalues of a symmetric  tridiagonal  matrix  T.
24       The  user may ask for all eigenvalues, all eigenvalues in the half-open
25       interval (VL, VU], or the IL-th through IU-th eigenvalues.
26
27       To avoid overflow, the matrix must be scaled so that its
28       largest element is no greater than overflow**(1/2) *
29       underflow**(1/4) in absolute value, and for greatest
30       accuracy, it should not be much smaller than that.
31
32       See W. Kahan "Accurate Eigenvalues of a Symmetric Tridiagonal  Matrix",
33       Report CS41, Computer Science Dept., Stanford
34       University, July 21, 1966.
35
36

ARGUMENTS

38       RANGE   (input) CHARACTER*1
39               = 'A': ("All")   all eigenvalues will be found.
40               = 'V': ("Value") all eigenvalues in the half-open interval (VL,
41               VU] will be found.  = 'I': ("Index") the  IL-th  through  IU-th
42               eigenvalues (of the entire matrix) will be found.
43
44       ORDER   (input) CHARACTER*1
45               =  'B':  ("By Block") the eigenvalues will be grouped by split-
46               off block (see IBLOCK, ISPLIT) and  ordered  from  smallest  to
47               largest  within the block.  = 'E': ("Entire matrix") the eigen‐
48               values for the entire matrix will be ordered from  smallest  to
49               largest.
50
51       N       (input) INTEGER
52               The order of the tridiagonal matrix T.  N >= 0.
53
54       VL      (input) DOUBLE PRECISION
55               VU       (input)  DOUBLE  PRECISION If RANGE='V', the lower and
56               upper bounds of the interval to be  searched  for  eigenvalues.
57               Eigenvalues  less than or equal to VL, or greater than VU, will
58               not be returned.  VL < VU.  Not referenced if RANGE  =  'A'  or
59               'I'.
60
61       IL      (input) INTEGER
62               IU      (input) INTEGER If RANGE='I', the indices (in ascending
63               order) of the smallest and largest eigenvalues to be  returned.
64               1  <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.  Not
65               referenced if RANGE = 'A' or 'V'.
66
67       ABSTOL  (input) DOUBLE PRECISION
68               The absolute tolerance for the eigenvalues.  An eigenvalue  (or
69               cluster)  is considered to be located if it has been determined
70               to lie in an interval whose width is ABSTOL or less.  If ABSTOL
71               is less than or equal to zero, then ULP*|T| will be used, where
72               |T| means the 1-norm of T.
73
74               Eigenvalues will be computed most accurately when ABSTOL is set
75               to twice the underflow threshold 2*DLAMCH('S'), not zero.
76
77       D       (input) DOUBLE PRECISION array, dimension (N)
78               The n diagonal elements of the tridiagonal matrix T.
79
80       E       (input) DOUBLE PRECISION array, dimension (N-1)
81               The (n-1) off-diagonal elements of the tridiagonal matrix T.
82
83       M       (output) INTEGER
84               The actual number of eigenvalues found. 0 <= M <= N.  (See also
85               the description of INFO=2,3.)
86
87       NSPLIT  (output) INTEGER
88               The number of diagonal blocks in the matrix T.  1 <= NSPLIT  <=
89               N.
90
91       W       (output) DOUBLE PRECISION array, dimension (N)
92               On  exit,  the first M elements of W will contain the eigenval‐
93               ues.  (DSTEBZ may use the remaining N-M elements as workspace.)
94
95       IBLOCK  (output) INTEGER array, dimension (N)
96               At each row/column j where E(j) is zero or small, the matrix  T
97               is  considered to split into a block diagonal matrix.  On exit,
98               if INFO = 0, IBLOCK(i) specifies to which block (from 1 to  the
99               number of blocks) the eigenvalue W(i) belongs.  (DSTEBZ may use
100               the remaining N-M elements as workspace.)
101
102       ISPLIT  (output) INTEGER array, dimension (N)
103               The splitting points, at which T breaks  up  into  submatrices.
104               The  first  submatrix  consists of rows/columns 1 to ISPLIT(1),
105               the second of rows/columns ISPLIT(1)+1 through ISPLIT(2), etc.,
106               and  the  NSPLIT-th consists of rows/columns ISPLIT(NSPLIT-1)+1
107               through ISPLIT(NSPLIT)=N.  (Only the first NSPLIT elements will
108               actually  be used, but since the user cannot know a priori what
109               value NSPLIT will have, N words must be reserved for ISPLIT.)
110
111       WORK    (workspace) DOUBLE PRECISION array, dimension (4*N)
112
113       IWORK   (workspace) INTEGER array, dimension (3*N)
114
115       INFO    (output) INTEGER
116               = 0:  successful exit
117               < 0:  if INFO = -i, the i-th argument had an illegal value
118               > 0:  some or all of the eigenvalues failed to converge or
119               were not computed:
120               =1 or 3: Bisection failed to  converge  for  some  eigenvalues;
121               these  eigenvalues are flagged by a negative block number.  The
122               effect is that the eigenvalues may not be as  accurate  as  the
123               absolute  and relative tolerances.  This is generally caused by
124               unexpectedly inaccurate arithmetic.  =2 or 3:  RANGE='I'  only:
125               Not all of the eigenvalues
126               IL:IU were found.
127               Effect: M < IU+1-IL
128               Cause:  non-monotonic arithmetic, causing the Sturm sequence to
129               be non-monotonic.  Cure:   recalculate,  using  RANGE='A',  and
130               pick
131               out eigenvalues IL:IU.  In some cases, increasing the PARAMETER
132               "FUDGE" may make things work.  = 4:    RANGE='I', and the  Ger‐
133               shgorin  interval initially used was too small.  No eigenvalues
134               were computed.  Probable cause: your machine has sloppy  float‐
135               ing-point  arithmetic.   Cure:  Increase the PARAMETER "FUDGE",
136               recompile, and try again.
137

PARAMETERS

139       RELFAC  DOUBLE PRECISION, default = 2.0e0
140               The relative tolerance.  An interval (a,b] lies  within  "rela‐
141               tive  tolerance" if  b-a < RELFAC*ulp*max(|a|,|b|), where "ulp"
142               is the machine precision (distance from 1 to  the  next  larger
143               floating point number.)
144
145       FUDGE   DOUBLE PRECISION, default = 2
146               A "fudge factor" to widen the Gershgorin intervals.  Ideally, a
147               value of 1 should work, but on machines with sloppy arithmetic,
148               this  needs  to  be  larger.  The default for publicly released
149               versions should be large enough to  handle  the  worst  machine
150               around.   Note that this has no effect on accuracy of the solu‐
151               tion.
152
153
154
155 LAPACK routine (version 3.1)    November 2006                       DSTEBZ(1)
Impressum