NAME

chsein - use inverse iteration to find specified right and/or left eigenvectors of a complex upper Hessenberg matrix H


SYNOPSIS

  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(*)

F95 INTERFACE

  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

C INTERFACE

#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);


PURPOSE

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.


ARGUMENTS


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|.