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

NAME

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

ARGUMENTS

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

FURTHER DETAILS

172       Based on contributions by
173          Inderjit Dhillon, IBM Almaden, USA
174          Osni Marques, LBNL/NERSC, USA
175          Ken Stanley, Computer Science Division, University of
176            California at Berkeley, USA
177
178
179
180 LAPACK driver routine (version 3.N2o)vember 2008                       DSTEVR(1)
Impressum