NAME

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


SYNOPSIS

  SUBROUTINE ZGGEV( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, VL, 
 *      LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO)
  CHARACTER * 1 JOBVL, JOBVR
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER N, LDA, LDB, LDVL, LDVR, LWORK, INFO
  DOUBLE PRECISION RWORK(*)
  SUBROUTINE ZGGEV_64( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, 
 *      VL, LDVL, VR, LDVR, WORK, LWORK, RWORK, INFO)
  CHARACTER * 1 JOBVL, JOBVR
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER*8 N, LDA, LDB, LDVL, LDVR, LWORK, INFO
  DOUBLE PRECISION RWORK(*)

F95 INTERFACE

  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(8), DIMENSION(:) :: ALPHA, BETA, WORK
  COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR
  INTEGER :: N, LDA, LDB, LDVL, LDVR, LWORK, INFO
  REAL(8), 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(8), DIMENSION(:) :: ALPHA, BETA, WORK
  COMPLEX(8), DIMENSION(:,:) :: A, B, VL, VR
  INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, LWORK, INFO
  REAL(8), DIMENSION(:) :: RWORK

C INTERFACE

#include <sunperf.h>

void zggev(char jobvl, char jobvr, int n, doublecomplex *a, int lda, doublecomplex *b, int ldb, doublecomplex *alpha, doublecomplex *beta, doublecomplex *vl, int ldvl, doublecomplex *vr, int ldvr, int *info);

void zggev_64(char jobvl, char jobvr, long n, doublecomplex *a, long lda, doublecomplex *b, long ldb, doublecomplex *alpha, doublecomplex *beta, doublecomplex *vl, long ldvl, doublecomplex *vr, long ldvr, long *info);


PURPOSE

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


ARGUMENTS