cggev - compute for a pair of N-by-N complex nonsymmetric matrices (A,B), the generalized eigenvalues, and optionally, the left and/or right generalized eigenvectors
SUBROUTINE CGGEV( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, VL, * LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO) CHARACTER * 1 JOBVL, JOBVR COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER N, LDA, LDB, LDVL, LDVR, LWORK, INFO REAL RWORK(*)
SUBROUTINE CGGEV_64( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, * VL, LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO) CHARACTER * 1 JOBVL, JOBVR COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), VL(LDVL,*), VR(LDVR,*), WORK(*) INTEGER*8 N, LDA, LDB, LDVL, LDVR, LWORK, INFO REAL RWORK(*)
SUBROUTINE GGEV( JOBVL, JOBVR, [N], A, [LDA], B, [LDB], ALPHA, BETA, * VL, [LDVL], VR, [LDVR], [WORK], [LWORK], [RWORK], [INFO]) CHARACTER(LEN=1) :: JOBVL, JOBVR COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK COMPLEX, DIMENSION(:,:) :: A, B, VL, VR INTEGER :: N, LDA, LDB, LDVL, LDVR, LWORK, INFO REAL, DIMENSION(:) :: RWORK
SUBROUTINE GGEV_64( JOBVL, JOBVR, [N], A, [LDA], B, [LDB], ALPHA, * BETA, VL, [LDVL], VR, [LDVR], [WORK], [LWORK], [RWORK], [INFO]) CHARACTER(LEN=1) :: JOBVL, JOBVR COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK COMPLEX, DIMENSION(:,:) :: A, B, VL, VR INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, LWORK, INFO REAL, DIMENSION(:) :: RWORK
#include <sunperf.h>
void cggev(char jobvl, char jobvr, int n, complex *a, int lda, complex *b, int ldb, complex *alpha, complex *beta, complex *vl, int ldvl, complex *vr, int ldvr, int *info);
void cggev_64(char jobvl, char jobvr, long n, complex *a, long lda, complex *b, long ldb, complex *alpha, complex *beta, complex *vl, long ldvl, complex *vr, long ldvr, long *info);
cggev computes for a pair of N-by-N complex nonsymmetric matrices (A,B), the generalized eigenvalues, and optionally, the left and/or right generalized eigenvectors.
A generalized eigenvalue for a pair of matrices (A,B) is a scalar lambda or a ratio alpha/beta = lambda, such that A - lambda*B is singular. It is usually represented as the pair (alpha,beta), as there is a reasonable interpretation for beta=0, and even for both being zero.
The right generalized eigenvector v(j)
corresponding to the
generalized eigenvalue lambda(j)
of (A,B) satisfies
A * v(j) = lambda(j) * B * v(j).
The left generalized eigenvector u(j)
corresponding to the
generalized eigenvalues lambda(j)
of (A,B) satisfies
u(j)**H * A = lambda(j) * u(j)**H * B
where u(j)**H is the conjugate-transpose of u(j).
= 'N': do not compute the left generalized eigenvectors;
= 'V': compute the left generalized eigenvectors.
= 'N': do not compute the right generalized eigenvectors;
= 'V': compute the right generalized eigenvectors.
Note: the quotients ALPHA(j)/BETA(j)
may easily over- or
underflow, and BETA(j)
may even be zero. Thus, the user
should avoid naively computing the ratio alpha/beta.
However, ALPHA will be always less than and usually
comparable with norm(A)
in magnitude, and BETA always less
than and usually comparable with norm(B).
u(j)
are
stored one after another in the columns of VL, in the same
order as their eigenvalues.
Each eigenvector will be scaled so the largest component
will have abs(real part) + abs(imag. part) = 1.
Not referenced if JOBVL = 'N'.
v(j)
are
stored one after another in the columns of VR, in the same
order as their eigenvalues.
Each eigenvector will be scaled so the largest component
will have abs(real part) + abs(imag. part) = 1.
Not referenced if JOBVR = 'N'.
WORK(1)
returns the optimal LWORK.
If LWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the WORK array, returns this value as the first entry of the WORK array, and no error message related to LWORK is issued by XERBLA.
dimension(8*N)
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value.
=1,...,N: The QZ iteration failed. No eigenvectors have been calculated, but ALPHA(j) and BETA(j) should be correct for j =INFO+1,...,N. > N: =N+1: other then QZ iteration failed in SHGEQZ,
=N+2: error return from STGEVC.