Contents


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, doub-
               lecomplex *alpha, doublecomplex *beta,  doublecom-
               plex *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

     JOBVL (input)
               = 'N':  do not compute the left generalized eigen-
               vectors;
               = 'V':  compute the left generalized eigenvectors.

     JOBVR (input)
               = 'N':   do  not  compute  the  right  generalized
               eigenvectors;
               = 'V':  compute the  right  generalized  eigenvec-
               tors.

     N (input) The order of the matrices A, B, VL, and VR.  N  >=
               0.

     A (input/output)
               On entry, the matrix A  in  the  pair  (A,B).   On
               exit, A has been overwritten.

     LDA (input)
               The leading dimension of A.  LDA >= max(1,N).

     B (input/output)
               On entry, the matrix B  in  the  pair  (A,B).   On
               exit, B has been overwritten.

     LDB (input)
               The leading dimension of B.  LDB >= max(1,N).

     ALPHA (output)
               On exit, ALPHA(j)/BETA(j), j=1,...,N, will be  the
               generalized eigenvalues.

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

     BETA (output)
               See description of ALPHA.

     VL (output)
               If JOBVL = 'V', the left generalized  eigenvectors
               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'.

     LDVL (input)
               The leading dimension of the matrix VL. LDVL >= 1,
               and if JOBVL = 'V', LDVL >= N.
     VR (output)
               If JOBVR = 'V', the right generalized eigenvectors
               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'.

     LDVR (input)
               The leading dimension of the matrix VR. LDVR >= 1,
               and if JOBVR = 'V', LDVR >= N.

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LWORK.

     LWORK (input)
               The  dimension  of  the  array  WORK.   LWORK   >=
               max(1,2*N).  For good performance, LWORK must gen-
               erally be larger.

               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.

     RWORK (workspace)
               dimension(8*N)

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               =1,...,N:  The QZ iteration failed.  No  eigenvec-
               tors   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.