NAME

dggevx - compute for a pair of N-by-N real nonsymmetric matrices (A,B)


SYNOPSIS

  SUBROUTINE DGGEVX( BALANC, JOBVL, JOBVR, SENSE, N, A, LDA, B, LDB, 
 *      ALPHAR, ALPHAI, BETA, VL, LDVL, VR, LDVR, ILO, IHI, LSCALE, 
 *      RSCALE, ABNRM, BBNRM, RCONDE, RCONDV, WORK, LWORK, IWORK, BWORK, 
 *      INFO)
  CHARACTER * 1 BALANC, JOBVL, JOBVR, SENSE
  INTEGER N, LDA, LDB, LDVL, LDVR, ILO, IHI, LWORK, INFO
  INTEGER IWORK(*)
  LOGICAL BWORK(*)
  DOUBLE PRECISION ABNRM, BBNRM
  DOUBLE PRECISION A(LDA,*), B(LDB,*), ALPHAR(*), ALPHAI(*), BETA(*), VL(LDVL,*), VR(LDVR,*), LSCALE(*), RSCALE(*), RCONDE(*), RCONDV(*), WORK(*)
  SUBROUTINE DGGEVX_64( BALANC, JOBVL, JOBVR, SENSE, N, A, LDA, B, 
 *      LDB, ALPHAR, ALPHAI, BETA, VL, LDVL, VR, LDVR, ILO, IHI, LSCALE, 
 *      RSCALE, ABNRM, BBNRM, RCONDE, RCONDV, WORK, LWORK, IWORK, BWORK, 
 *      INFO)
  CHARACTER * 1 BALANC, JOBVL, JOBVR, SENSE
  INTEGER*8 N, LDA, LDB, LDVL, LDVR, ILO, IHI, LWORK, INFO
  INTEGER*8 IWORK(*)
  LOGICAL*8 BWORK(*)
  DOUBLE PRECISION ABNRM, BBNRM
  DOUBLE PRECISION A(LDA,*), B(LDB,*), ALPHAR(*), ALPHAI(*), BETA(*), VL(LDVL,*), VR(LDVR,*), LSCALE(*), RSCALE(*), RCONDE(*), RCONDV(*), WORK(*)

F95 INTERFACE

  SUBROUTINE GGEVX( BALANC, JOBVL, JOBVR, SENSE, [N], A, [LDA], B, 
 *       [LDB], ALPHAR, ALPHAI, BETA, VL, [LDVL], VR, [LDVR], ILO, IHI, 
 *       LSCALE, RSCALE, ABNRM, BBNRM, RCONDE, RCONDV, [WORK], [LWORK], 
 *       [IWORK], [BWORK], [INFO])
  CHARACTER(LEN=1) :: BALANC, JOBVL, JOBVR, SENSE
  INTEGER :: N, LDA, LDB, LDVL, LDVR, ILO, IHI, LWORK, INFO
  INTEGER, DIMENSION(:) :: IWORK
  LOGICAL, DIMENSION(:) :: BWORK
  REAL(8) :: ABNRM, BBNRM
  REAL(8), DIMENSION(:) :: ALPHAR, ALPHAI, BETA, LSCALE, RSCALE, RCONDE, RCONDV, WORK
  REAL(8), DIMENSION(:,:) :: A, B, VL, VR
  SUBROUTINE GGEVX_64( BALANC, JOBVL, JOBVR, SENSE, [N], A, [LDA], B, 
 *       [LDB], ALPHAR, ALPHAI, BETA, VL, [LDVL], VR, [LDVR], ILO, IHI, 
 *       LSCALE, RSCALE, ABNRM, BBNRM, RCONDE, RCONDV, [WORK], [LWORK], 
 *       [IWORK], [BWORK], [INFO])
  CHARACTER(LEN=1) :: BALANC, JOBVL, JOBVR, SENSE
  INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, ILO, IHI, LWORK, INFO
  INTEGER(8), DIMENSION(:) :: IWORK
  LOGICAL(8), DIMENSION(:) :: BWORK
  REAL(8) :: ABNRM, BBNRM
  REAL(8), DIMENSION(:) :: ALPHAR, ALPHAI, BETA, LSCALE, RSCALE, RCONDE, RCONDV, WORK
  REAL(8), DIMENSION(:,:) :: A, B, VL, VR

C INTERFACE

#include <sunperf.h>

void dggevx(char balanc, char jobvl, char jobvr, char sense, int n, double *a, int lda, double *b, int ldb, double *alphar, double *alphai, double *beta, double *vl, int ldvl, double *vr, int ldvr, int *ilo, int *ihi, double *lscale, double *rscale, double *abnrm, double *bbnrm, double *rconde, double *rcondv, int *info);

void dggevx_64(char balanc, char jobvl, char jobvr, char sense, long n, double *a, long lda, double *b, long ldb, double *alphar, double *alphai, double *beta, double *vl, long ldvl, double *vr, long ldvr, long *ilo, long *ihi, double *lscale, double *rscale, double *abnrm, double *bbnrm, double *rconde, double *rcondv, long *info);


PURPOSE

dggevx computes for a pair of N-by-N real nonsymmetric matrices (A,B) the generalized eigenvalues, and optionally, the left and/or right generalized eigenvectors.

Optionally also, it computes a balancing transformation to improve the conditioning of the eigenvalues and eigenvectors (ILO, IHI, LSCALE, RSCALE, ABNRM, and BBNRM), reciprocal condition numbers for the eigenvalues (RCONDE), and reciprocal condition numbers for the right eigenvectors (RCONDV).

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 eigenvector v(j) corresponding to the eigenvalue lambda(j) of (A,B) satisfies

                 A * v(j) = lambda(j) * B * v(j) .

The left eigenvector u(j) corresponding to the eigenvalue 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


FURTHER DETAILS

Balancing a matrix pair (A,B) includes, first, permuting rows and columns to isolate eigenvalues, second, applying diagonal similarity transformation to the rows and columns to make the rows and columns as close in norm as possible. The computed reciprocal condition numbers correspond to the balanced matrix. Permuting rows and columns will not change the condition numbers (in exact arithmetic) but diagonal scaling will. For further explanation of balancing, see section 4.11.1.2 of LAPACK Users' Guide.

An approximate error bound on the chordal distance between the i-th computed generalized eigenvalue w and the corresponding exact eigenvalue lambda is

hord(w, lambda) < = EPS * norm(ABNRM, BBNRM) / RCONDE(I)

An approximate error bound for the angle between the i-th computed eigenvector VL(i) or VR(i) is given by

PS * norm(ABNRM, BBNRM) / DIF(i).

For further explanation of the reciprocal condition numbers RCONDE and RCONDV, see section 4.11 of LAPACK User's Guide.