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

NAME

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

SYNOPSIS

10       SUBROUTINE DLARRD( 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           DOUBLE         PRECISION PIVMIN, RELTOL, VL, VU, WL, WU
19
20           INTEGER        IBLOCK( * ), INDEXW( * ), ISPLIT( * ), IWORK( * )
21
22           DOUBLE         PRECISION D( * ), E( * ), E2( * ), GERS( * ),  W(  *
23                          ), WERR( * ), WORK( * )
24

PURPOSE

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

PARAMETERS

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