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

NAME

6       DSBGVX  -  selected eigenvalues, and optionally, eigenvectors of a real
7       generalized  symmetric-definite  banded  eigenproblem,  of   the   form
8       A*x=(lambda)*B*x
9

SYNOPSIS

11       SUBROUTINE DSBGVX( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, Q,
12                          LDQ, VL, VU, IL, IU, ABSTOL, M,  W,  Z,  LDZ,  WORK,
13                          IWORK, IFAIL, INFO )
14
15           CHARACTER      JOBZ, RANGE, UPLO
16
17           INTEGER        IL, INFO, IU, KA, KB, LDAB, LDBB, LDQ, LDZ, M, N
18
19           DOUBLE         PRECISION ABSTOL, VL, VU
20
21           INTEGER        IFAIL( * ), IWORK( * )
22
23           DOUBLE         PRECISION AB( LDAB, * ), BB( LDBB, * ), Q( LDQ, * ),
24                          W( * ), WORK( * ), Z( LDZ, * )
25

PURPOSE

27       DSBGVX computes selected eigenvalues, and optionally, eigenvectors of a
28       real  generalized  symmetric-definite  banded eigenproblem, of the form
29       A*x=(lambda)*B*x.  Here A and B are assumed to be symmetric and banded,
30       and  B  is also positive definite.  Eigenvalues and eigenvectors can be
31       selected by specifying either all eigenvalues, a range of values  or  a
32       range of indices for the desired eigenvalues.
33
34

ARGUMENTS

36       JOBZ    (input) CHARACTER*1
37               = 'N':  Compute eigenvalues only;
38               = 'V':  Compute eigenvalues and eigenvectors.
39
40       RANGE   (input) CHARACTER*1
41               = 'A': all eigenvalues will be found.
42               =  'V':  all eigenvalues in the half-open interval (VL,VU] will
43               be found.  = 'I': the IL-th through IU-th eigenvalues  will  be
44               found.
45
46       UPLO    (input) CHARACTER*1
47               = 'U':  Upper triangles of A and B are stored;
48               = 'L':  Lower triangles of A and B are stored.
49
50       N       (input) INTEGER
51               The order of the matrices A and B.  N >= 0.
52
53       KA      (input) INTEGER
54               The  number of superdiagonals of the matrix A if UPLO = 'U', or
55               the number of subdiagonals if UPLO = 'L'.  KA >= 0.
56
57       KB      (input) INTEGER
58               The number of superdiagonals of the matrix B if UPLO = 'U',  or
59               the number of subdiagonals if UPLO = 'L'.  KB >= 0.
60
61       AB      (input/output) DOUBLE PRECISION array, dimension (LDAB, N)
62               On  entry,  the  upper  or lower triangle of the symmetric band
63               matrix A, stored in the first ka+1 rows of the array.  The j-th
64               column  of  A  is  stored in the j-th column of the array AB as
65               follows: if UPLO = 'U', AB(ka+1+i-j,j) =  A(i,j)  for  max(1,j-
66               ka)<=i<=j;   if   UPLO  =  'L',  AB(1+i-j,j)     =  A(i,j)  for
67               j<=i<=min(n,j+ka).
68
69               On exit, the contents of AB are destroyed.
70
71       LDAB    (input) INTEGER
72               The leading dimension of the array AB.  LDAB >= KA+1.
73
74       BB      (input/output) DOUBLE PRECISION array, dimension (LDBB, N)
75               On entry, the upper or lower triangle  of  the  symmetric  band
76               matrix B, stored in the first kb+1 rows of the array.  The j-th
77               column of B is stored in the j-th column of  the  array  BB  as
78               follows:  if  UPLO  = 'U', BB(ka+1+i-j,j) = B(i,j) for max(1,j-
79               kb)<=i<=j;  if  UPLO  =  'L',  BB(1+i-j,j)     =   B(i,j)   for
80               j<=i<=min(n,j+kb).
81
82               On exit, the factor S from the split Cholesky factorization B =
83               S**T*S, as returned by DPBSTF.
84
85       LDBB    (input) INTEGER
86               The leading dimension of the array BB.  LDBB >= KB+1.
87
88       Q       (output) DOUBLE PRECISION array, dimension (LDQ, N)
89               If JOBZ = 'V', the n-by-n matrix used in the reduction of A*x =
90               (lambda)*B*x  to standard form, i.e. C*x = (lambda)*x, and con‐
91               sequently C to tridiagonal form.  If JOBZ = 'N', the array Q is
92               not referenced.
93
94       LDQ     (input) INTEGER
95               The leading dimension of the array Q.  If JOBZ = 'N', LDQ >= 1.
96               If JOBZ = 'V', LDQ >= max(1,N).
97
98       VL      (input) DOUBLE PRECISION
99               VU      (input) DOUBLE PRECISION If RANGE='V',  the  lower  and
100               upper bounds of the interval to be searched for eigenvalues. VL
101               < VU.  Not referenced if RANGE = 'A' or 'I'.
102
103       IL      (input) INTEGER
104               IU      (input) INTEGER If RANGE='I', the indices (in ascending
105               order)  of the smallest and largest eigenvalues to be returned.
106               1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.   Not
107               referenced if RANGE = 'A' or 'V'.
108
109       ABSTOL  (input) DOUBLE PRECISION
110               The  absolute error tolerance for the eigenvalues.  An approxi‐
111               mate eigenvalue is accepted as converged when it is  determined
112               to lie in an interval [a,b] of width less than or equal to
113
114               ABSTOL + EPS *   max( |a|,|b| ) ,
115
116               where  EPS is the machine precision.  If ABSTOL is less than or
117               equal to zero, then  EPS*|T|  will be used in its place,  where
118               |T|  is the 1-norm of the tridiagonal matrix obtained by reduc‐
119               ing A to tridiagonal form.
120
121               Eigenvalues will be computed most accurately when ABSTOL is set
122               to  twice  the underflow threshold 2*DLAMCH('S'), not zero.  If
123               this routine returns with INFO>0, indicating that  some  eigen‐
124               vectors did not converge, try setting ABSTOL to 2*DLAMCH('S').
125
126       M       (output) INTEGER
127               The  total number of eigenvalues found.  0 <= M <= N.  If RANGE
128               = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
129
130       W       (output) DOUBLE PRECISION array, dimension (N)
131               If INFO = 0, the eigenvalues in ascending order.
132
133       Z       (output) DOUBLE PRECISION array, dimension (LDZ, N)
134               If JOBZ = 'V', then if INFO = 0, Z contains  the  matrix  Z  of
135               eigenvectors, with the i-th column of Z holding the eigenvector
136               associated with  W(i).   The  eigenvectors  are  normalized  so
137               Z**T*B*Z = I.  If JOBZ = 'N', then Z is not referenced.
138
139       LDZ     (input) INTEGER
140               The  leading dimension of the array Z.  LDZ >= 1, and if JOBZ =
141               'V', LDZ >= max(1,N).
142
143       WORK    (workspace/output) DOUBLE PRECISION array, dimension (7*N)
144
145       IWORK   (workspace/output) INTEGER array, dimension (5*N)
146
147       IFAIL   (output) INTEGER array, dimension (M)
148               If JOBZ = 'V', then if INFO = 0, the first M elements of  IFAIL
149               are  zero.  If INFO > 0, then IFAIL contains the indices of the
150               eigenvalues that failed to converge.  If JOBZ = 'N', then IFAIL
151               is not referenced.
152
153       INFO    (output) INTEGER
154               = 0 : successful exit
155               < 0 : if INFO = -i, the i-th argument had an illegal value
156               <=  N:  if  INFO  =  i, then i eigenvectors failed to converge.
157               Their indices are stored in IFAIL.  > N :  DPBSTF  returned  an
158               error  code;  i.e.,  if INFO = N + i, for 1 <= i <= N, then the
159               leading minor of order i of B is not  positive  definite.   The
160               factorization of B could not be completed and no eigenvalues or
161               eigenvectors were computed.
162

FURTHER DETAILS

164       Based on contributions by
165          Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
166
167
168
169
170 LAPACK driver routine (version 3.N1o)vember 2006                       DSBGVX(1)
Impressum