dsbgvx - compute selected eigenvalues, and optionally, eigenvectors of a real generalized symmetric-definite banded eigenproblem, of the form A*x=(lambda)*B*x
SUBROUTINE DSBGVX( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, * Q, LDQ, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, IWORK, IFAIL, * INFO) CHARACTER * 1 JOBZ, RANGE, UPLO INTEGER N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO INTEGER IWORK(*), IFAIL(*) DOUBLE PRECISION VL, VU, ABSTOL DOUBLE PRECISION AB(LDAB,*), BB(LDBB,*), Q(LDQ,*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE DSBGVX_64( JOBZ, RANGE, UPLO, N, KA, KB, AB, LDAB, BB, * LDBB, Q, LDQ, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, IWORK, * IFAIL, INFO) CHARACTER * 1 JOBZ, RANGE, UPLO INTEGER*8 N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO INTEGER*8 IWORK(*), IFAIL(*) DOUBLE PRECISION VL, VU, ABSTOL DOUBLE PRECISION AB(LDAB,*), BB(LDBB,*), Q(LDQ,*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE SBGVX( JOBZ, RANGE, UPLO, [N], KA, KB, AB, [LDAB], BB, * [LDBB], Q, [LDQ], VL, VU, IL, IU, ABSTOL, M, W, Z, [LDZ], [WORK], * [IWORK], IFAIL, [INFO]) CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO INTEGER :: N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO INTEGER, DIMENSION(:) :: IWORK, IFAIL REAL(8) :: VL, VU, ABSTOL REAL(8), DIMENSION(:) :: W, WORK REAL(8), DIMENSION(:,:) :: AB, BB, Q, Z
SUBROUTINE SBGVX_64( JOBZ, RANGE, UPLO, [N], KA, KB, AB, [LDAB], BB, * [LDBB], Q, [LDQ], VL, VU, IL, IU, ABSTOL, M, W, Z, [LDZ], [WORK], * [IWORK], IFAIL, [INFO]) CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO INTEGER(8) :: N, KA, KB, LDAB, LDBB, LDQ, IL, IU, M, LDZ, INFO INTEGER(8), DIMENSION(:) :: IWORK, IFAIL REAL(8) :: VL, VU, ABSTOL REAL(8), DIMENSION(:) :: W, WORK REAL(8), DIMENSION(:,:) :: AB, BB, Q, Z
#include <sunperf.h>
void dsbgvx(char jobz, char range, char uplo, int n, int ka, int kb, double *ab, int ldab, double *bb, int ldbb, double *q, int ldq, double vl, double vu, int il, int iu, double abstol, int *m, double *w, double *z, int ldz, int *ifail, int *info);
void dsbgvx_64(char jobz, char range, char uplo, long n, long ka, long kb, double *ab, long ldab, double *bb, long ldbb, double *q, long ldq, double vl, double vu, long il, long iu, double abstol, long *m, double *w, double *z, long ldz, long *ifail, long *info);
dsbgvx computes selected eigenvalues, and optionally, eigenvectors of a real generalized symmetric-definite banded eigenproblem, of the form A*x=(lambda)*B*x. Here A and B are assumed to be symmetric and banded, and B is also positive definite. Eigenvalues and eigenvectors can be selected by specifying either all eigenvalues, a range of values or a range of indices for the desired eigenvalues.
= 'N': Compute eigenvalues only;
= 'V': Compute eigenvalues and eigenvectors.
= 'A': all eigenvalues will be found.
= 'V': all eigenvalues in the half-open interval (VL,VU] will be found. = 'I': the IL-th through IU-th eigenvalues will be found.
= 'U': Upper triangles of A and B are stored;
= 'L': Lower triangles of A and B are stored.
AB(ka+1+i-j,j)
= A(i,j)
for max(1,j-ka)
< =i < =j;
if UPLO = 'L', AB(1+i-j,j)
= A(i,j)
for j < =i < =min(n,j+ka).
On exit, the contents of AB are destroyed.
BB(ka+1+i-j,j)
= B(i,j)
for max(1,j-kb)
< =i < =j;
if UPLO = 'L', BB(1+i-j,j)
= B(i,j)
for j < =i < =min(n,j+kb).
On exit, the factor S from the split Cholesky factorization B = S**T*S, as returned by SPBSTF.
ABSTOL + EPS * max( |a|,|b| ) ,
where EPS is the machine precision. If ABSTOL is less than or equal to zero, then EPS*|T| will be used in its place, where |T| is the 1-norm of the tridiagonal matrix obtained by reducing A to tridiagonal form.
Eigenvalues will be computed most accurately when ABSTOL is set to twice the underflow threshold 2*SLAMCH('S'), not zero. If this routine returns with INFO >0, indicating that some eigenvectors did not converge, try setting ABSTOL to 2*SLAMCH('S').
dimension(7*N)
dimension(5*N)
= 0 : successful exit
< 0 : if INFO = -i, the i-th argument had an illegal value
< = N: if INFO = i, then i eigenvectors failed to converge. Their indices are stored in IFAIL. > N : SPBSTF returned an error code; i.e., if INFO = N + i, for 1 < = i < = N, then the leading minor of order i of B is not positive definite. The factorization of B could not be completed and no eigenvalues or eigenvectors were computed.
Based on contributions by
Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA