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

NAME

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

SYNOPSIS

11       SUBROUTINE SSBGVX( 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           REAL           ABSTOL, VL, VU
20
21           INTEGER        IFAIL( * ), IWORK( * )
22
23           REAL           AB(  LDAB,  * ), BB( LDBB, * ), Q( LDQ, * ), W( * ),
24                          WORK( * ), Z( LDZ, * )
25

PURPOSE

27       SSBGVX 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

ARGUMENTS

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

FURTHER DETAILS

155       Based on contributions by
156          Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
157
158
159
160 LAPACK driver routine (version 3.N2o)vember 2008                       SSBGVX(1)
Impressum