chsein - use inverse iteration to find specified right and/or left eigenvectors of a complex upper Hessenberg matrix H
SUBROUTINE CHSEIN( SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL, * LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO) CHARACTER * 1 SIDE, EIGSRC, INITV COMPLEX H(LDH,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER N, LDH, LDVL, LDVR, MM, M, INFO INTEGER IFAILL(*), IFAILR(*) LOGICAL SELECT(*) REAL RWORK(*)
SUBROUTINE CHSEIN_64( SIDE, EIGSRC, INITV, SELECT, N, H, LDH, W, VL, * LDVL, VR, LDVR, MM, M, WORK, RWORK, IFAILL, IFAILR, INFO) CHARACTER * 1 SIDE, EIGSRC, INITV COMPLEX H(LDH,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER*8 N, LDH, LDVL, LDVR, MM, M, INFO INTEGER*8 IFAILL(*), IFAILR(*) LOGICAL*8 SELECT(*) REAL RWORK(*)
SUBROUTINE HSEIN( SIDE, EIGSRC, INITV, SELECT, [N], H, [LDH], W, VL, * [LDVL], VR, [LDVR], MM, M, [WORK], [RWORK], IFAILL, IFAILR, [INFO]) CHARACTER(LEN=1) :: SIDE, EIGSRC, INITV COMPLEX, DIMENSION(:) :: W, WORK COMPLEX, DIMENSION(:,:) :: H, VL, VR INTEGER :: N, LDH, LDVL, LDVR, MM, M, INFO INTEGER, DIMENSION(:) :: IFAILL, IFAILR LOGICAL, DIMENSION(:) :: SELECT REAL, DIMENSION(:) :: RWORK
SUBROUTINE HSEIN_64( SIDE, EIGSRC, INITV, SELECT, [N], H, [LDH], W, * VL, [LDVL], VR, [LDVR], MM, M, [WORK], [RWORK], IFAILL, IFAILR, * [INFO]) CHARACTER(LEN=1) :: SIDE, EIGSRC, INITV COMPLEX, DIMENSION(:) :: W, WORK COMPLEX, DIMENSION(:,:) :: H, VL, VR INTEGER(8) :: N, LDH, LDVL, LDVR, MM, M, INFO INTEGER(8), DIMENSION(:) :: IFAILL, IFAILR LOGICAL(8), DIMENSION(:) :: SELECT REAL, DIMENSION(:) :: RWORK
#include <sunperf.h>
void chsein(char side, char eigsrc, char initv, logical *select, int n, complex *h, int ldh, complex *w, complex *vl, int ldvl, complex *vr, int ldvr, int mm, int *m, int *ifaill, int *ifailr, int *info);
void chsein_64(char side, char eigsrc, char initv, logical *select, long n, complex *h, long ldh, complex *w, complex *vl, long ldvl, complex *vr, long ldvr, long mm, long *m, long *ifaill, long *ifailr, long *info);
chsein uses inverse iteration to find specified right and/or left eigenvectors of a complex upper Hessenberg matrix H.
The right eigenvector x and the left eigenvector y of the matrix H corresponding to an eigenvalue w are defined by:
H * x = w * x, y**h * H = w * y**h
where y**h denotes the conjugate transpose of the vector y.
= 'R': compute right eigenvectors only;
= 'L': compute left eigenvectors only;
= 'B': compute both right and left eigenvectors.
= 'Q': the eigenvalues were found using CHSEQR; thus, if H has zero subdiagonal elements, and so is block-triangular, then the j-th eigenvalue can be assumed to be an eigenvalue of the block containing the j-th row/column. This property allows CHSEIN to perform inverse iteration on just one diagonal block. = 'N': no assumptions are made on the correspondence between eigenvalues and diagonal blocks. In this case, CHSEIN must always perform inverse iteration using the whole matrix H.
= 'N': no initial vectors are supplied;
= 'U': user-supplied initial vectors are stored in the arrays VL and/or VR.
SELECT(j)
must be set to .TRUE..
max(1,N)
if SIDE = 'L' or 'B'; LDVL > = 1 otherwise.
max(1,N)
if SIDE = 'R' or 'B'; LDVR > = 1 otherwise.
dimension(N*N)
dimension(N)
IFAILL(i)
= j > 0 if the left
eigenvector in the i-th column of VL (corresponding to the
eigenvalue w(j))
failed to converge; IFAILL(i)
= 0 if the
eigenvector converged satisfactorily.
If SIDE = 'R', IFAILL is not referenced.
IFAILR(i)
= j > 0 if the right
eigenvector in the i-th column of VR (corresponding to the
eigenvalue w(j))
failed to converge; IFAILR(i)
= 0 if the
eigenvector converged satisfactorily.
If SIDE = 'L', IFAILR is not referenced.
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value
> 0: if INFO = i, i is the number of eigenvectors which failed to converge; see IFAILL and IFAILR for further details.
Each eigenvector is normalized so that the element of largest magnitude has magnitude 1; here the magnitude of a complex number (x,y) is taken to be |x|+|y|.