ctgevc - compute some or all of the right and/or left generalized eigenvectors of a pair of complex upper triangular matrices (A,B)
SUBROUTINE CTGEVC( SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, * LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO) CHARACTER * 1 SIDE, HOWMNY COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL SELECT(*) REAL RWORK(*)
SUBROUTINE CTGEVC_64( SIDE, HOWMNY, SELECT, N, A, LDA, B, LDB, VL, * LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO) CHARACTER * 1 SIDE, HOWMNY COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER*8 N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL*8 SELECT(*) REAL RWORK(*)
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, DIMENSION(:) :: WORK COMPLEX, DIMENSION(:,:) :: A, B, VL, VR INTEGER :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL, DIMENSION(:) :: SELECT REAL, 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, DIMENSION(:) :: WORK COMPLEX, DIMENSION(:,:) :: A, B, VL, VR INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, MM, M, INFO LOGICAL(8), DIMENSION(:) :: SELECT REAL, DIMENSION(:) :: RWORK
#include <sunperf.h>
void ctgevc(char side, char howmny, logical *select, int n, complex *a, int lda, complex *b, int ldb, complex *vl, int ldvl, complex *vr, int ldvr, int mm, int *m, int *info);
void ctgevc_64(char side, char howmny, logical *select, long n, complex *a, long lda, complex *b, long ldb, complex *vl, long ldvl, complex *vr, long ldvr, long mm, long *m, long *info);
ctgevc 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.
= 'R': compute right eigenvectors only;
= 'L': compute left eigenvectors only;
= 'B': compute both right and left eigenvectors.
= 'A': compute all right and/or left eigenvectors;
= 'B': compute all right and/or left eigenvectors, and backtransform them using the input matrices supplied in VR and/or VL; = 'S': compute selected right and/or left eigenvectors, specified by the logical array SELECT.
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(2*N)
dimension(2*N)
= 0: successful exit.
< 0: if INFO = -i, the i-th argument had an illegal value.