NAME

ztgevc - compute some or all of the right and/or left generalized eigenvectors of a pair of complex upper triangular matrices (A,B)


SYNOPSIS

  SUBROUTINE ZTGEVC( SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, 
 *      LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO)
  CHARACTER * 1 SIDE, HOWMNY
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER N, LDA, LDB, LDVL, LDVR, MM, M, INFO
  LOGICAL SELECT(*)
  DOUBLE PRECISION RWORK(*)
  SUBROUTINE ZTGEVC_64( SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, 
 *      LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO)
  CHARACTER * 1 SIDE, HOWMNY
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER*8 N, LDA, LDB, LDVL, LDVR, MM, M, INFO
  LOGICAL*8 SELECT(*)
  DOUBLE PRECISION RWORK(*)

F95 INTERFACE

  SUBROUTINE TGEVC( SIDE, HOWMNY, SELECT, [N], A, [LDA], B, [LDB], VL, 
 *       [LDVL], VR, [LDVR], MM, M, [WORK], [RWORK], [INFO])
  CHARACTER(LEN=1) :: SIDE, HOWMNY
  COMPLEX(8), DIMENSION(:) :: WORK
  COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR
  INTEGER :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO
  LOGICAL, DIMENSION(:) :: SELECT
  REAL(8), DIMENSION(:) :: RWORK
  SUBROUTINE TGEVC_64( SIDE, HOWMNY, SELECT, [N], A, [LDA], B, [LDB], 
 *       VL, [LDVL], VR, [LDVR], MM, M, [WORK], [RWORK], [INFO])
  CHARACTER(LEN=1) :: SIDE, HOWMNY
  COMPLEX(8), DIMENSION(:) :: WORK
  COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR
  INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO
  LOGICAL(8), DIMENSION(:) :: SELECT
  REAL(8), DIMENSION(:) :: RWORK

C INTERFACE

#include <sunperf.h>

void ztgevc(char side, char howmny, logical *select, int n, doublecomplex *a, int lda, doublecomplex *b, int ldb, doublecomplex *vl, int ldvl, doublecomplex *vr, int ldvr, int mm, int *m, int *info);

void ztgevc_64(char side, char howmny, logical *select, long n, doublecomplex *a, long lda, doublecomplex *b, long ldb, doublecomplex *vl, long ldvl, doublecomplex *vr, long ldvr, long mm, long *m, long *info);


PURPOSE

ztgevc computes some or all of the right and/or left generalized eigenvectors of a pair of complex upper triangular matrices (A,B).

The right generalized eigenvector x and the left generalized eigenvector y of (A,B) corresponding to a generalized eigenvalue w are defined by:

        (A - wB) * x = 0  and  y**H * (A - wB) = 0

where y**H denotes the conjugate tranpose of y.

If an eigenvalue w is determined by zero diagonal elements of both A and B, a unit vector is returned as the corresponding eigenvector.

If all eigenvectors are requested, the routine may either return the matrices X and/or Y of right or left eigenvectors of (A,B), or the products Z*X and/or Q*Y, where Z and Q are input unitary matrices. If (A,B) was obtained from the generalized Schur factorization of an original pair of matrices

   (A0,B0) = (Q*A*Z**H,Q*B*Z**H),

then Z*X and Q*Y are the matrices of right or left eigenvectors of A.


ARGUMENTS