ssyevx - compute selected eigenvalues and, optionally, eigenvectors of a real symmetric matrix A
SUBROUTINE SSYEVX( JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU, * ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, IWORK2, IFAIL, INFO) CHARACTER * 1 JOBZ, RANGE, UPLO INTEGER N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO INTEGER IWORK2(*), IFAIL(*) REAL VL, VU, ABTOL REAL A(LDA,*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE SSYEVX_64( JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU, * ABTOL, NFOUND, W, Z, LDZ, WORK, LDWORK, IWORK2, IFAIL, INFO) CHARACTER * 1 JOBZ, RANGE, UPLO INTEGER*8 N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO INTEGER*8 IWORK2(*), IFAIL(*) REAL VL, VU, ABTOL REAL A(LDA,*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE SYEVX( JOBZ, RANGE, UPLO, [N], A, [LDA], VL, VU, IL, IU, * ABTOL, NFOUND, W, Z, [LDZ], [WORK], [LDWORK], [IWORK2], IFAIL, * [INFO]) CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO INTEGER :: N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO INTEGER, DIMENSION(:) :: IWORK2, IFAIL REAL :: VL, VU, ABTOL REAL, DIMENSION(:) :: W, WORK REAL, DIMENSION(:,:) :: A, Z
SUBROUTINE SYEVX_64( JOBZ, RANGE, UPLO, [N], A, [LDA], VL, VU, IL, * IU, ABTOL, NFOUND, W, Z, [LDZ], [WORK], [LDWORK], [IWORK2], * IFAIL, [INFO]) CHARACTER(LEN=1) :: JOBZ, RANGE, UPLO INTEGER(8) :: N, LDA, IL, IU, NFOUND, LDZ, LDWORK, INFO INTEGER(8), DIMENSION(:) :: IWORK2, IFAIL REAL :: VL, VU, ABTOL REAL, DIMENSION(:) :: W, WORK REAL, DIMENSION(:,:) :: A, Z
#include <sunperf.h>
void ssyevx(char jobz, char range, char uplo, int n, float *a, int lda, float vl, float vu, int il, int iu, float abtol, int *nfound, float *w, float *z, int ldz, int *ifail, int *info);
void ssyevx_64(char jobz, char range, char uplo, long n, float *a, long lda, float vl, float vu, long il, long iu, float abtol, long *nfound, float *w, float *z, long ldz, long *ifail, long *info);
ssyevx computes selected eigenvalues and, optionally, eigenvectors of a real symmetric 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.
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.
WORK(1)
returns the optimal LDWORK.
If LDWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the WORK array, returns this value as the first entry of the WORK array, and no error message related to LDWORK is issued by XERBLA.
= 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.