1SLARRD(1)           LAPACK auxiliary routine (version 3.1)           SLARRD(1)
2
3
4

NAME

6       SLARRD  -  the eigenvalues of a symmetric tridiagonal matrix T to suit‐
7       able accuracy
8

SYNOPSIS

10       SUBROUTINE SLARRD( RANGE, ORDER, N, VL, VU, IL, IU, GERS, RELTOL, D, E,
11                          E2,  PIVMIN,  NSPLIT,  ISPLIT,  M,  W, WERR, WL, WU,
12                          IBLOCK, INDEXW, WORK, IWORK, INFO )
13
14           CHARACTER      ORDER, RANGE
15
16           INTEGER        IL, INFO, IU, M, N, NSPLIT
17
18           REAL           PIVMIN, RELTOL, VL, VU, WL, WU
19
20           INTEGER        IBLOCK( * ), INDEXW( * ), ISPLIT( * ), IWORK( * )
21
22           REAL           D( * ), E( * ), E2( * ), GERS( * ), W( * ), WERR(  *
23                          ), WORK( * )
24

PURPOSE

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

ARGUMENTS

43       RANGE   (input) CHARACTER
44               = 'A': ("All")   all eigenvalues will be found.
45               = 'V': ("Value") all eigenvalues in the half-open interval (VL,
46               VU]  will  be  found.  = 'I': ("Index") the IL-th through IU-th
47               eigenvalues (of the entire matrix) will be found.
48
49       ORDER   (input) CHARACTER
50               = 'B': ("By Block") the eigenvalues will be grouped  by  split-
51               off  block  (see  IBLOCK,  ISPLIT) and ordered from smallest to
52               largest within the block.  = 'E': ("Entire matrix") the  eigen‐
53               values  for  the entire matrix will be ordered from smallest to
54               largest.
55
56       N       (input) INTEGER
57               The order of the tridiagonal matrix T.  N >= 0.
58
59       VL      (input) REAL
60               VU      (input) REAL If RANGE='V', the lower and  upper  bounds
61               of  the  interval  to be searched for eigenvalues.  Eigenvalues
62               less than or equal to VL, or  greater  than  VU,  will  not  be
63               returned.  VL < VU.  Not referenced if RANGE = 'A' or 'I'.
64
65       IL      (input) INTEGER
66               IU      (input) INTEGER If RANGE='I', the indices (in ascending
67               order) of the smallest and largest eigenvalues to be  returned.
68               1  <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.  Not
69               referenced if RANGE = 'A' or 'V'.
70
71       GERS    (input) REAL             array, dimension (2*N)
72               The N Gerschgorin intervals (the i-th Gerschgorin  interval  is
73               (GERS(2*i-1), GERS(2*i)).
74
75       RELTOL  (input) REAL
76               The minimum relative width of an interval.  When an interval is
77               narrower than RELTOL times the larger (in magnitude)  endpoint,
78               then  it  is  considered  to  be sufficiently small, i.e., con‐
79               verged.  Note: this should always  be  at  least  radix*machine
80               epsilon.
81
82       D       (input) REAL             array, dimension (N)
83               The n diagonal elements of the tridiagonal matrix T.
84
85       E       (input) REAL             array, dimension (N-1)
86               The (n-1) off-diagonal elements of the tridiagonal matrix T.
87
88       E2      (input) REAL             array, dimension (N-1)
89               The  (n-1)  squared  off-diagonal  elements  of the tridiagonal
90               matrix T.
91
92       PIVMIN  (input) REAL
93               The minimum pivot allowed in the Sturm sequence for T.
94
95       NSPLIT  (input) INTEGER
96               The number of diagonal blocks in the matrix T.  1 <= NSPLIT  <=
97               N.
98
99       ISPLIT  (input) INTEGER array, dimension (N)
100               The  splitting  points,  at which T breaks up into submatrices.
101               The first submatrix consists of rows/columns  1  to  ISPLIT(1),
102               the second of rows/columns ISPLIT(1)+1 through ISPLIT(2), etc.,
103               and the NSPLIT-th consists of  rows/columns  ISPLIT(NSPLIT-1)+1
104               through ISPLIT(NSPLIT)=N.  (Only the first NSPLIT elements will
105               actually be used, but since the user cannot know a priori  what
106               value NSPLIT will have, N words must be reserved for ISPLIT.)
107
108       M       (output) INTEGER
109               The actual number of eigenvalues found. 0 <= M <= N.  (See also
110               the description of INFO=2,3.)
111
112       W       (output) REAL             array, dimension (N)
113               On exit, the first M elements of W will contain the  eigenvalue
114               approximations.  SLARRD  computes  an interval I_j = (a_j, b_j]
115               that includes eigenvalue j.  The  eigenvalue  approximation  is
116               given as the interval midpoint W(j)= ( a_j + b_j)/2. The corre‐
117               sponding error is bounded by WERR(j) = abs( a_j - b_j)/2
118
119       WERR    (output) REAL             array, dimension (N)
120               The error bound on the corresponding  eigenvalue  approximation
121               in W.
122
123       WL      (output) REAL
124               WU       (output)  REAL  The interval (WL, WU] contains all the
125               wanted eigenvalues.  If RANGE='V', then WL=VL  and  WU=VU.   If
126               RANGE='A',  then WL and WU are the global Gerschgorin bounds on
127               the spectrum.  If RANGE='I', then WL and  WU  are  computed  by
128               SLAEBZ from the index range specified.
129
130       IBLOCK  (output) INTEGER array, dimension (N)
131               At  each row/column j where E(j) is zero or small, the matrix T
132               is considered to split into a block diagonal matrix.  On  exit,
133               if  INFO = 0, IBLOCK(i) specifies to which block (from 1 to the
134               number of blocks) the eigenvalue W(i) belongs.  (SLARRD may use
135               the remaining N-M elements as workspace.)
136
137       INDEXW  (output) INTEGER array, dimension (N)
138               The  indices  of the eigenvalues within each block (submatrix);
139               for example, INDEXW(i)= j and IBLOCK(i)=k imply that  the  i-th
140               eigenvalue W(i) is the j-th eigenvalue in block k.
141
142       WORK    (workspace) REAL             array, dimension (4*N)
143
144       IWORK   (workspace) INTEGER array, dimension (3*N)
145
146       INFO    (output) INTEGER
147               = 0:  successful exit
148               < 0:  if INFO = -i, the i-th argument had an illegal value
149               > 0:  some or all of the eigenvalues failed to converge or
150               were not computed:
151               =1  or  3:  Bisection  failed to converge for some eigenvalues;
152               these eigenvalues are flagged by a negative block number.   The
153               effect  is  that  the eigenvalues may not be as accurate as the
154               absolute and relative tolerances.  This is generally caused  by
155               unexpectedly  inaccurate  arithmetic.  =2 or 3: RANGE='I' only:
156               Not all of the eigenvalues
157               IL:IU were found.
158               Effect: M < IU+1-IL
159               Cause:  non-monotonic arithmetic, causing the Sturm sequence to
160               be  non-monotonic.   Cure:    recalculate, using RANGE='A', and
161               pick
162               out eigenvalues IL:IU.  In some cases, increasing the PARAMETER
163               "FUDGE"  may make things work.  = 4:    RANGE='I', and the Ger‐
164               shgorin interval initially used was too small.  No  eigenvalues
165               were  computed.  Probable cause: your machine has sloppy float‐
166               ing-point arithmetic.  Cure: Increase  the  PARAMETER  "FUDGE",
167               recompile, and try again.
168

PARAMETERS

170       FUDGE   REAL            , default = 2
171               A "fudge factor" to widen the Gershgorin intervals.  Ideally, a
172               value of 1 should work, but on machines with sloppy arithmetic,
173               this  needs  to  be  larger.  The default for publicly released
174               versions should be large enough to  handle  the  worst  machine
175               around.   Note that this has no effect on accuracy of the solu‐
176               tion.
177
178               Based on contributions by W. Kahan, University  of  California,
179               Berkeley,  USA  Beresford  Parlett,  University  of California,
180               Berkeley, USA Jim Demmel, University of  California,  Berkeley,
181               USA  Inderjit  Dhillon,  University  of Texas, Austin, USA Osni
182               Marques, LBNL/NERSC, USA Christof Voemel, University  of  Cali‐
183               fornia, Berkeley, USA
184
185
186
187 LAPACK auxiliary routine (versionNo3v.e1m)ber 2006                       SLARRD(1)
Impressum