NAME

cgegv - routine is deprecated and has been replaced by routine CGGEV


SYNOPSIS

  SUBROUTINE CGEGV( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, VL, 
 *      LDVL, VR, LDVR, WORK, LDWORK, WORK2, INFO)
  CHARACTER * 1 JOBVL, JOBVR
  COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER N, LDA, LDB, LDVL, LDVR, LDWORK, INFO
  REAL WORK2(*)
  SUBROUTINE CGEGV_64( JOBVL, JOBVR, N, A, LDA, B, LDB, ALPHA, BETA, 
 *      VL, LDVL, VR, LDVR, WORK, LDWORK, WORK2, INFO)
  CHARACTER * 1 JOBVL, JOBVR
  COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER*8 N, LDA, LDB, LDVL, LDVR, LDWORK, INFO
  REAL WORK2(*)

F95 INTERFACE

  SUBROUTINE GEGV( JOBVL, JOBVR, [N], A, [LDA], B, [LDB], ALPHA, BETA, 
 *       VL, [LDVL], VR, [LDVR], [WORK], [LDWORK], [WORK2], [INFO])
  CHARACTER(LEN=1) :: JOBVL, JOBVR
  COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK
  COMPLEX, DIMENSION(:,:) :: A, B, VL, VR
  INTEGER :: N, LDA, LDB, LDVL, LDVR, LDWORK, INFO
  REAL, DIMENSION(:) :: WORK2
  SUBROUTINE GEGV_64( JOBVL, JOBVR, [N], A, [LDA], B, [LDB], ALPHA, 
 *       BETA, VL, [LDVL], VR, [LDVR], [WORK], [LDWORK], [WORK2], [INFO])
  CHARACTER(LEN=1) :: JOBVL, JOBVR
  COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK
  COMPLEX, DIMENSION(:,:) :: A, B, VL, VR
  INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, LDWORK, INFO
  REAL, DIMENSION(:) :: WORK2

C INTERFACE

#include <sunperf.h>

void cgegv(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 cgegv_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);


PURPOSE

cgegv routine is deprecated and has been replaced by routine CGGEV.

CGEGV computes for a pair of N-by-N complex nonsymmetric matrices A and B, the generalized eigenvalues (alpha, beta), and optionally, the left and/or right generalized eigenvectors (VL and VR).

A generalized eigenvalue for a pair of matrices (A,B) is, roughly speaking, a scalar w or a ratio alpha/beta = w, such that A - w*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. A good beginning reference is the book, ``Matrix Computations'', by G. Golub & C. van Loan (Johns Hopkins U. Press)

A right generalized eigenvector corresponding to a generalized eigenvalue w for a pair of matrices (A,B) is a vector r such that (A - w B) r = 0 . A left generalized eigenvector is a vector l such that l**H * (A - w B) = 0, where l**H is the

conjugate-transpose of l.

Note: this routine performs ``full balancing'' on A and B. See ``Further Details'', below.


ARGUMENTS


FURTHER DETAILS

Balancing

---------

This driver calls CGGBAL to both permute and scale rows and columns of A and B. The permutations PL and PR are chosen so that PL*A*PR and PL*B*R will be upper triangular except for the diagonal blocks A(i:j,i:j) and B(i:j,i:j), with i and j as close together as possible. The diagonal scaling matrices DL and DR are chosen so that the pair DL*PL*A*PR*DR, DL*PL*B*PR*DR have elements close to one (except for the elements that start out zero.)

After the eigenvalues and eigenvectors of the balanced matrices have been computed, CGGBAK transforms the eigenvectors back to what they would have been (in perfect arithmetic) if they had not been balanced.

Contents of A and B on Exit

-------- -- - --- - -- ----

If any eigenvectors are computed (either JOBVL ='V' or JOBVR ='V' or both), then on exit the arrays A and B will contain the complex Schur form[*] of the ``balanced'' versions of A and B. If no eigenvectors are computed, then only the diagonal blocks will be correct.

[*] In other words, upper triangular form.