dstein - compute the eigenvectors of a real symmetric tridiagonal matrix T corresponding to specified eigenvalues, using inverse iteration
SUBROUTINE DSTEIN( N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, * IWORK, IFAIL, INFO) INTEGER N, M, LDZ, INFO INTEGER IBLOCK(*), ISPLIT(*), IWORK(*), IFAIL(*) DOUBLE PRECISION D(*), E(*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE DSTEIN_64( N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, * IWORK, IFAIL, INFO) INTEGER*8 N, M, LDZ, INFO INTEGER*8 IBLOCK(*), ISPLIT(*), IWORK(*), IFAIL(*) DOUBLE PRECISION D(*), E(*), W(*), Z(LDZ,*), WORK(*)
SUBROUTINE STEIN( [N], D, E, [M], W, IBLOCK, ISPLIT, Z, [LDZ], [WORK], * [IWORK], IFAIL, [INFO]) INTEGER :: N, M, LDZ, INFO INTEGER, DIMENSION(:) :: IBLOCK, ISPLIT, IWORK, IFAIL REAL(8), DIMENSION(:) :: D, E, W, WORK REAL(8), DIMENSION(:,:) :: Z
SUBROUTINE STEIN_64( [N], D, E, [M], W, IBLOCK, ISPLIT, Z, [LDZ], * [WORK], [IWORK], IFAIL, [INFO]) INTEGER(8) :: N, M, LDZ, INFO INTEGER(8), DIMENSION(:) :: IBLOCK, ISPLIT, IWORK, IFAIL REAL(8), DIMENSION(:) :: D, E, W, WORK REAL(8), DIMENSION(:,:) :: Z
#include <sunperf.h>
void dstein(int n, double *d, double *e, int m, double *w, int *iblock, int *isplit, double *z, int ldz, int *ifail, int *info);
void dstein_64(long n, double *d, double *e, long m, double *w, long *iblock, long *isplit, double *z, long ldz, long *ifail, long *info);
dstein computes the eigenvectors of a real symmetric tridiagonal matrix T corresponding to specified eigenvalues, using inverse iteration.
The maximum number of iterations allowed for each eigenvector is specified by an internal parameter MAXITS (currently set to 5).
E(N)
need not be set.
IBLOCK(i)
=1 if eigenvalue W(i)
belongs to
the first submatrix from the top, =2 if W(i)
belongs to
the second submatrix, etc. ( The output array IBLOCK
from SSTEBZ is expected here. )
W(i)
is stored in the i-th column of
Z. Any vector which fails to converge is set to its current
iterate after MAXITS iterations.
dimension(5*N)
dimension(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 in MAXITS iterations. Their indices are stored in array IFAIL.