1DSTEVR(1)             LAPACK driver routine (version 3.1)            DSTEVR(1)
2
3
4

NAME

6       DSTEVR  -  selected eigenvalues and, optionally, eigenvectors of a real
7       symmetric tridiagonal matrix T
8

SYNOPSIS

10       SUBROUTINE DSTEVR( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL, M,  W,
11                          Z, LDZ, ISUPPZ, WORK, LWORK, IWORK, LIWORK, INFO )
12
13           CHARACTER      JOBZ, RANGE
14
15           INTEGER        IL, INFO, IU, LDZ, LIWORK, LWORK, M, N
16
17           DOUBLE         PRECISION ABSTOL, VL, VU
18
19           INTEGER        ISUPPZ( * ), IWORK( * )
20
21           DOUBLE         PRECISION D( * ), E( * ), W( * ), WORK( * ), Z( LDZ,
22                          * )
23

PURPOSE

25       DSTEVR computes selected eigenvalues and, optionally, eigenvectors of a
26       real  symmetric tridiagonal matrix T.  Eigenvalues and eigenvectors can
27       be selected by specifying either a  range  of  values  or  a  range  of
28       indices for the desired eigenvalues.
29
30       Whenever possible, DSTEVR calls DSTEMR to compute the
31       eigenspectrum using Relatively Robust Representations.  DSTEMR computes
32       eigenvalues by the dqds algorithm, while  orthogonal  eigenvectors  are
33       computed  from  various  "good"  L D L^T representations (also known as
34       Relatively Robust Representations). Gram-Schmidt  orthogonalization  is
35       avoided as far as possible. More specifically, the various steps of the
36       algorithm are as follows. For the i-th unreduced block of T,
37          (a) Compute T - sigma_i = L_i D_i L_i^T, such that L_i D_i L_i^T
38               is a relatively robust representation,
39          (b) Compute the eigenvalues, lambda_j, of L_i D_i L_i^T to high
40              relative accuracy by the dqds algorithm,
41          (c) If there is a cluster of close eigenvalues, "choose" sigma_i
42              close to the cluster, and go to step (a),
43          (d) Given the approximate eigenvalue lambda_j of L_i D_i L_i^T,
44              compute the corresponding eigenvector by forming a
45              rank-revealing twisted factorization.
46       The desired accuracy of the output can be specified by the input param‐
47       eter ABSTOL.
48
49       For  more details, see "A new O(n^2) algorithm for the symmetric tridi‐
50       agonal eigenvalue/eigenvector problem", by Inderjit  Dhillon,  Computer
51       Science Division Technical Report No. UCB//CSD-97-971, UC Berkeley, May
52       1997.
53
54
55       Note 1 : DSTEVR calls DSTEMR when the full  spectrum  is  requested  on
56       machines which conform to the ieee-754 floating point standard.  DSTEVR
57       calls DSTEBZ and DSTEIN on non-ieee machines and
58       when partial spectrum requests are made.
59
60       Normal execution of DSTEMR may create NaNs and infinities and hence may
61       abort  due  to  a floating point exception in environments which do not
62       handle NaNs and infinities in the ieee standard default manner.
63
64

ARGUMENTS

66       JOBZ    (input) CHARACTER*1
67               = 'N':  Compute eigenvalues only;
68               = 'V':  Compute eigenvalues and eigenvectors.
69
70       RANGE   (input) CHARACTER*1
71               = 'A': all eigenvalues will be found.
72               = 'V': all eigenvalues in the half-open interval  (VL,VU]  will
73               be  found.   = 'I': the IL-th through IU-th eigenvalues will be
74               found.
75
76       N       (input) INTEGER
77               The order of the matrix.  N >= 0.
78
79       D       (input/output) DOUBLE PRECISION array, dimension (N)
80               On entry, the n diagonal elements of the tridiagonal matrix  A.
81               On  exit,  D  may  be multiplied by a constant factor chosen to
82               avoid over/underflow in computing the eigenvalues.
83
84       E       (input/output) DOUBLE PRECISION array, dimension (max(1,N-1))
85               On entry, the (n-1) subdiagonal  elements  of  the  tridiagonal
86               matrix  A  in elements 1 to N-1 of E.  On exit, E may be multi‐
87               plied by a constant factor chosen to  avoid  over/underflow  in
88               computing the eigenvalues.
89
90       VL      (input) DOUBLE PRECISION
91               VU       (input)  DOUBLE  PRECISION If RANGE='V', the lower and
92               upper bounds of the interval to be searched for eigenvalues. VL
93               < VU.  Not referenced if RANGE = 'A' or 'I'.
94
95       IL      (input) INTEGER
96               IU      (input) INTEGER If RANGE='I', the indices (in ascending
97               order) of the smallest and largest eigenvalues to be  returned.
98               1  <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.  Not
99               referenced if RANGE = 'A' or 'V'.
100
101       ABSTOL  (input) DOUBLE PRECISION
102               The absolute error tolerance for the eigenvalues.  An  approxi‐
103               mate  eigenvalue is accepted as converged when it is determined
104               to lie in an interval [a,b] of width less than or equal to
105
106               ABSTOL + EPS *   max( |a|,|b| ) ,
107
108               where EPS is the machine precision.  If ABSTOL is less than  or
109               equal  to zero, then  EPS*|T|  will be used in its place, where
110               |T| is the 1-norm of the tridiagonal matrix obtained by  reduc‐
111               ing A to tridiagonal form.
112
113               See  "Computing  Small  Singular  Values of Bidiagonal Matrices
114               with Guaranteed High Relative Accuracy," by Demmel  and  Kahan,
115               LAPACK Working Note #3.
116
117               If  high  relative accuracy is important, set ABSTOL to DLAMCH(
118               'Safe minimum' ).  Doing so will guarantee that eigenvalues are
119               computed  to  high  relative  accuracy  when possible in future
120               releases.  The current code does not make any guarantees  about
121               high relative accuracy, but future releases will. See J. Barlow
122               and J. Demmel, "Computing Accurate Eigensystems of Scaled Diag‐
123               onally  Dominant  Matrices", LAPACK Working Note #7, for a dis‐
124               cussion of which matrices define their eigenvalues to high rel‐
125               ative accuracy.
126
127       M       (output) INTEGER
128               The  total number of eigenvalues found.  0 <= M <= N.  If RANGE
129               = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
130
131       W       (output) DOUBLE PRECISION array, dimension (N)
132               The first  M  elements  contain  the  selected  eigenvalues  in
133               ascending order.
134
135       Z       (output) DOUBLE PRECISION array, dimension (LDZ, max(1,M) )
136               If  JOBZ = 'V', then if INFO = 0, the first M columns of Z con‐
137               tain the orthonormal eigenvectors of the matrix A corresponding
138               to  the selected eigenvalues, with the i-th column of Z holding
139               the eigenvector associated with  W(i).   Note:  the  user  must
140               ensure that at least max(1,M) columns are supplied in the array
141               Z; if RANGE = 'V', the exact value of M is not known in advance
142               and an upper bound must be used.
143
144       LDZ     (input) INTEGER
145               The  leading dimension of the array Z.  LDZ >= 1, and if JOBZ =
146               'V', LDZ >= max(1,N).
147
148       ISUPPZ  (output) INTEGER array, dimension ( 2*max(1,M) )
149               The support of the eigenvectors in Z, i.e., the  indices  indi‐
150               cating  the  nonzero  elements  in  Z.  The i-th eigenvector is
151               nonzero only in elements ISUPPZ( 2*i-1 ) through ISUPPZ( 2*i ).
152
153       WORK      (workspace/output)   DOUBLE   PRECISION   array,    dimension
154       (MAX(1,LWORK))
155               On exit, if INFO = 0, WORK(1) returns the optimal (and minimal)
156               LWORK.
157
158       LWORK   (input) INTEGER
159               The dimension of the array WORK.  LWORK >= max(1,20*N).
160
161               If LWORK = -1, then a workspace query is assumed;  the  routine
162               only calculates the optimal sizes of the WORK and IWORK arrays,
163               returns these values as the first entries of the WORK and IWORK
164               arrays,  and  no  error  message  related to LWORK or LIWORK is
165               issued by XERBLA.
166
167       IWORK   (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
168               On exit, if INFO = 0, IWORK(1) returns the optimal  (and  mini‐
169               mal) LIWORK.
170
171       LIWORK  (input) INTEGER
172               The dimension of the array IWORK.  LIWORK >= max(1,10*N).
173
174               If  LIWORK = -1, then a workspace query is assumed; the routine
175               only calculates the optimal sizes of the WORK and IWORK arrays,
176               returns these values as the first entries of the WORK and IWORK
177               arrays, and no error message related  to  LWORK  or  LIWORK  is
178               issued by XERBLA.
179
180       INFO    (output) INTEGER
181               = 0:  successful exit
182               < 0:  if INFO = -i, the i-th argument had an illegal value
183               > 0:  Internal error
184

FURTHER DETAILS

186       Based on contributions by
187          Inderjit Dhillon, IBM Almaden, USA
188          Osni Marques, LBNL/NERSC, USA
189          Ken Stanley, Computer Science Division, University of
190            California at Berkeley, USA
191
192
193
194
195 LAPACK driver routine (version 3.N1o)vember 2006                       DSTEVR(1)
Impressum