chbevx - compute selected eigenvalues and, optionally, eigenvectors of a complex Hermitian band matrix A
SUBROUTINE CHBEVX( JOBZ, RANGE, UPLO, N, NDIAG, A, LDA, Q, LDQ, VL, * VU, IL, IU, ABTOL, NFOUND, W, Z, LDZ, WORK, WORK2, IWORK3, IFAIL, * INFO) CHARACTER * 1 JOBZ, RANGE, UPLO COMPLEX A(LDA,*), Q(LDQ,*), Z(LDZ,*), WORK(*) INTEGER N, NDIAG, LDA, LDQ, IL, IU, NFOUND, LDZ, INFO INTEGER IWORK3(*), IFAIL(*) REAL VL, VU, ABTOL REAL W(*), WORK2(*)
SUBROUTINE CHBEVX_64( JOBZ, RANGE, UPLO, N, NDIAG, A, LDA, Q, LDQ, * VL, VU, IL, IU, ABTOL, NFOUND, W, Z, LDZ, WORK, WORK2, IWORK3, * IFAIL, INFO) CHARACTER * 1 JOBZ, RANGE, UPLO COMPLEX A(LDA,*), Q(LDQ,*), Z(LDZ,*), WORK(*) INTEGER*8 N, NDIAG, LDA, LDQ, IL, IU, NFOUND, LDZ, INFO INTEGER*8 IWORK3(*), IFAIL(*) REAL VL, VU, ABTOL REAL W(*), WORK2(*)
SUBROUTINE HBEVX( JOBZ, RANGE, UPLO, [N], NDIAG, A, [LDA], Q, [LDQ], * VL, VU, IL, IU, ABTOL, [NFOUND], W, Z, [LDZ], [WORK], [WORK2], * [IWORK3], IFAIL, [INFO]) CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO COMPLEX, DIMENSION(:) :: WORK COMPLEX, DIMENSION(:,:) :: A, Q, Z INTEGER :: N, NDIAG, LDA, LDQ, IL, IU, NFOUND, LDZ, INFO INTEGER, DIMENSION(:) :: IWORK3, IFAIL REAL :: VL, VU, ABTOL REAL, DIMENSION(:) :: W, WORK2
SUBROUTINE HBEVX_64( JOBZ, RANGE, UPLO, [N], NDIAG, A, [LDA], Q, * [LDQ], VL, VU, IL, IU, ABTOL, [NFOUND], W, Z, [LDZ], [WORK], * [WORK2], [IWORK3], IFAIL, [INFO]) CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO COMPLEX, DIMENSION(:) :: WORK COMPLEX, DIMENSION(:,:) :: A, Q, Z INTEGER(8) :: N, NDIAG, LDA, LDQ, IL, IU, NFOUND, LDZ, INFO INTEGER(8), DIMENSION(:) :: IWORK3, IFAIL REAL :: VL, VU, ABTOL REAL, DIMENSION(:) :: W, WORK2
#include <sunperf.h>
void chbevx(char jobz, char range, char uplo, int n, int ndiag, complex *a, int lda, complex *q, int ldq, float vl, float vu, int il, int iu, float abtol, int *nfound, float *w, complex *z, int ldz, int *ifail, int *info);
void chbevx_64(char jobz, char range, char uplo, long n, long ndiag, complex *a, long lda, complex *q, long ldq, float vl, float vu, long il, long iu, float abtol, long *nfound, float *w, complex *z, long ldz, long *ifail, long *info);
chbevx computes selected eigenvalues and, optionally, eigenvectors of a complex Hermitian band matrix A. Eigenvalues and eigenvectors can be selected by specifying either 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 triangle of A is stored;
= 'L': Lower triangle of A is stored.
A(kd+1+i-j,j)
= A(i,j)
for max(1,j-kd)
< =i < =j;
if UPLO = 'L', A(1+i-j,j)
= A(i,j)
for j < =i < =min(n,j+kd).
On exit, A is overwritten by values generated during the reduction to tridiagonal form.
ABTOL + EPS * max( |a|,|b| ) ,
where EPS is the machine precision. If ABTOL 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 ABTOL 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 ABTOL to 2*SLAMCH('S').
See ``Computing Small Singular Values of Bidiagonal Matrices with Guaranteed High Relative Accuracy,'' by Demmel and Kahan, LAPACK Working Note #3.
max(1,NFOUND)
columns are
supplied in the array Z; if RANGE = 'V', the exact value of NFOUND
is not known in advance and an upper bound must be used.
dimension(N)
dimension(7*N)
dimension(5*N)
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value
> 0: if INFO = i, then i eigenvectors failed to converge. Their indices are stored in array IFAIL.