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

NAME

6       SSBEVX  -  selected eigenvalues and, optionally, eigenvectors of a real
7       symmetric band matrix A
8

SYNOPSIS

10       SUBROUTINE SSBEVX( JOBZ, RANGE, UPLO, N, KD, AB, LDAB, Q, LDQ, VL,  VU,
11                          IL,  IU,  ABSTOL,  M, W, Z, LDZ, WORK, IWORK, IFAIL,
12                          INFO )
13
14           CHARACTER      JOBZ, RANGE, UPLO
15
16           INTEGER        IL, INFO, IU, KD, LDAB, LDQ, LDZ, M, N
17
18           REAL           ABSTOL, VL, VU
19
20           INTEGER        IFAIL( * ), IWORK( * )
21
22           REAL           AB( LDAB, * ), Q( LDQ, * ), W( * ), WORK(  *  ),  Z(
23                          LDZ, * )
24

PURPOSE

26       SSBEVX computes selected eigenvalues and, optionally, eigenvectors of a
27       real symmetric band matrix A.   Eigenvalues  and  eigenvectors  can  be
28       selected  by  specifying either a range of values or a range of indices
29       for the desired eigenvalues.
30
31

ARGUMENTS

33       JOBZ    (input) CHARACTER*1
34               = 'N':  Compute eigenvalues only;
35               = 'V':  Compute eigenvalues and eigenvectors.
36
37       RANGE   (input) CHARACTER*1
38               = 'A': all eigenvalues will be found;
39               = 'V': all eigenvalues in the half-open interval  (VL,VU]  will
40               be  found;  =  'I': the IL-th through IU-th eigenvalues will be
41               found.
42
43       UPLO    (input) CHARACTER*1
44               = 'U':  Upper triangle of A is stored;
45               = 'L':  Lower triangle of A is stored.
46
47       N       (input) INTEGER
48               The order of the matrix A.  N >= 0.
49
50       KD      (input) INTEGER
51               The number of superdiagonals of the matrix A if UPLO = 'U',  or
52               the number of subdiagonals if UPLO = 'L'.  KD >= 0.
53
54       AB      (input/output) REAL array, dimension (LDAB, N)
55               On  entry,  the  upper  or lower triangle of the symmetric band
56               matrix A, stored in the first KD+1 rows of the array.  The j-th
57               column  of  A  is  stored in the j-th column of the array AB as
58               follows: if UPLO = 'U', AB(kd+1+i-j,j) =  A(i,j)  for  max(1,j-
59               kd)<=i<=j;   if   UPLO  =  'L',  AB(1+i-j,j)     =  A(i,j)  for
60               j<=i<=min(n,j+kd).
61
62               On exit, AB is  overwritten  by  values  generated  during  the
63               reduction to tridiagonal form.  If UPLO = 'U', the first super‐
64               diagonal and the diagonal  of  the  tridiagonal  matrix  T  are
65               returned  in  rows  KD  and  KD+1 of AB, and if UPLO = 'L', the
66               diagonal and first subdiagonal of T are returned in  the  first
67               two rows of AB.
68
69       LDAB    (input) INTEGER
70               The leading dimension of the array AB.  LDAB >= KD + 1.
71
72       Q       (output) REAL array, dimension (LDQ, N)
73               If  JOBZ = 'V', the N-by-N orthogonal matrix used in the reduc‐
74               tion to tridiagonal form.  If JOBZ = 'N', the array  Q  is  not
75               referenced.
76
77       LDQ     (input) INTEGER
78               The  leading dimension of the array Q.  If JOBZ = 'V', then LDQ
79               >= max(1,N).
80
81       VL      (input) REAL
82               VU      (input) REAL If RANGE='V', the lower and  upper  bounds
83               of  the  interval to be searched for eigenvalues. VL < VU.  Not
84               referenced if RANGE = 'A' or 'I'.
85
86       IL      (input) INTEGER
87               IU      (input) INTEGER If RANGE='I', the indices (in ascending
88               order)  of the smallest and largest eigenvalues to be returned.
89               1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.   Not
90               referenced if RANGE = 'A' or 'V'.
91
92       ABSTOL  (input) REAL
93               The  absolute error tolerance for the eigenvalues.  An approxi‐
94               mate eigenvalue is accepted as converged when it is  determined
95               to lie in an interval [a,b] of width less than or equal to
96
97               ABSTOL + EPS *   max( |a|,|b| ) ,
98
99               where  EPS is the machine precision.  If ABSTOL is less than or
100               equal to zero, then  EPS*|T|  will be used in its place,  where
101               |T|  is the 1-norm of the tridiagonal matrix obtained by reduc‐
102               ing AB to tridiagonal form.
103
104               Eigenvalues will be computed most accurately when ABSTOL is set
105               to  twice  the underflow threshold 2*SLAMCH('S'), not zero.  If
106               this routine returns with INFO>0, indicating that  some  eigen‐
107               vectors did not converge, try setting ABSTOL to 2*SLAMCH('S').
108
109               See  "Computing  Small  Singular  Values of Bidiagonal Matrices
110               with Guaranteed High Relative Accuracy," by Demmel  and  Kahan,
111               LAPACK Working Note #3.
112
113       M       (output) INTEGER
114               The  total number of eigenvalues found.  0 <= M <= N.  If RANGE
115               = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
116
117       W       (output) REAL array, dimension (N)
118               The first  M  elements  contain  the  selected  eigenvalues  in
119               ascending order.
120
121       Z       (output) REAL array, dimension (LDZ, max(1,M))
122               If  JOBZ = 'V', then if INFO = 0, the first M columns of Z con‐
123               tain the orthonormal eigenvectors of the matrix A corresponding
124               to  the selected eigenvalues, with the i-th column of Z holding
125               the eigenvector associated with W(i).  If an eigenvector  fails
126               to converge, then that column of Z contains the latest approxi‐
127               mation to the eigenvector, and the index of the eigenvector  is
128               returned  in  IFAIL.   If JOBZ = 'N', then Z is not referenced.
129               Note: the user must ensure that at least max(1,M)  columns  are
130               supplied  in  the array Z; if RANGE = 'V', the exact value of M
131               is not known in advance and an upper bound must be used.
132
133       LDZ     (input) INTEGER
134               The leading dimension of the array Z.  LDZ >= 1, and if JOBZ  =
135               'V', LDZ >= max(1,N).
136
137       WORK    (workspace) REAL array, dimension (7*N)
138
139       IWORK   (workspace) INTEGER array, dimension (5*N)
140
141       IFAIL   (output) INTEGER array, dimension (N)
142               If  JOBZ = 'V', then if INFO = 0, the first M elements of IFAIL
143               are zero.  If INFO > 0, then IFAIL contains the indices of  the
144               eigenvectors  that  failed  to  converge.   If JOBZ = 'N', then
145               IFAIL is not referenced.
146
147       INFO    (output) INTEGER
148               = 0:  successful exit.
149               < 0:  if INFO = -i, the i-th argument had an illegal value.
150               > 0:  if INFO = i, then  i  eigenvectors  failed  to  converge.
151               Their indices are stored in array IFAIL.
152
153
154
155 LAPACK driver routine (version 3.N1o)vember 2006                       SSBEVX(1)
Impressum