Contents


NAME

     sgegs - routine is deprecated and has been replaced by  rou-
     tine SGGES

SYNOPSIS

     SUBROUTINE SGEGS(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHAR, ALPHAI,
           BETA, VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, INFO)

     CHARACTER * 1 JOBVSL, JOBVSR
     INTEGER N, LDA, LDB, LDVSL, LDVSR, LDWORK, INFO
     REAL  A(LDA,*),  B(LDB,*),  ALPHAR(*),  ALPHAI(*),  BETA(*),
     VSL(LDVSL,*), VSR(LDVSR,*), WORK(*)

     SUBROUTINE SGEGS_64(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHAR,
           ALPHAI, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, INFO)

     CHARACTER * 1 JOBVSL, JOBVSR
     INTEGER*8 N, LDA, LDB, LDVSL, LDVSR, LDWORK, INFO
     REAL  A(LDA,*),  B(LDB,*),  ALPHAR(*),  ALPHAI(*),  BETA(*),
     VSL(LDVSL,*), VSR(LDVSR,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE GEGS(JOBVSL, JOBVSR, [N], A, [LDA], B, [LDB], ALPHAR,
            ALPHAI, BETA, VSL, [LDVSL], VSR, [LDVSR], [WORK], [LDWORK], [INFO])

     CHARACTER(LEN=1) :: JOBVSL, JOBVSR
     INTEGER :: N, LDA, LDB, LDVSL, LDVSR, LDWORK, INFO
     REAL, DIMENSION(:) :: ALPHAR, ALPHAI, BETA, WORK
     REAL, DIMENSION(:,:) :: A, B, VSL, VSR

     SUBROUTINE GEGS_64(JOBVSL, JOBVSR, [N], A, [LDA], B, [LDB], ALPHAR,
            ALPHAI, BETA, VSL, [LDVSL], VSR, [LDVSR], [WORK], [LDWORK], [INFO])

     CHARACTER(LEN=1) :: JOBVSL, JOBVSR
     INTEGER(8) :: N, LDA, LDB, LDVSL, LDVSR, LDWORK, INFO
     REAL, DIMENSION(:) :: ALPHAR, ALPHAI, BETA, WORK
     REAL, DIMENSION(:,:) :: A, B, VSL, VSR

  C INTERFACE
     #include <sunperf.h>

     void sgegs(char jobvsl, char jobvsr, int n,  float  *a,  int
               lda,  float  *b,  int  ldb,  float  *alphar, float
               *alphai, float *beta, float *vsl, int ldvsl, float
               *vsr, int ldvsr, int *info);
     void sgegs_64(char jobvsl, char jobvsr, long  n,  float  *a,
               long lda, float *b, long ldb, float *alphar, float
               *alphai, float  *beta,  float  *vsl,  long  ldvsl,
               float *vsr, long ldvsr, long *info);

PURPOSE

     sgegs routine is deprecated and has been replaced by routine
     SGGES.

     SGEGS computes  for  a  pair  of  N-by-N  real  nonsymmetric
     matrices  A,  B:   the  generalized  eigenvalues (alphar +/-
     alphai*i, beta), the real Schur form (A, B), and  optionally
     left and/or right Schur vectors (VSL and VSR).

     (If only the generalized eigenvalues  are  needed,  use  the
     driver SGEGV instead.)

     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 interpre-
     tation 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)

     The (generalized) Schur form of a pair of  matrices  is  the
     result  of  multiplying  both  matrices  on  the left by one
     orthogonal matrix and both on the right by another  orthogo-
     nal matrix, these two orthogonal matrices being chosen so as
     to bring the pair of matrices into (real) Schur form.

     A pair of matrices A, B is in generalized real Schur form if
     B  is  upper  triangular with non-negative diagonal and A is
     block upper triangular with 1-by-1 and  2-by-2  blocks.   1-
     by-1  blocks  correspond  to  real  generalized eigenvalues,
     while 2-by-2 blocks of A will be  "standardized"  by  making
     the corresponding elements of B have the form:
             [  a  0  ]
             [  0  b  ]

     and the pair of corresponding 2-by-2 blocks in A and B  will
     have a complex conjugate pair of generalized eigenvalues.

     The left and right Schur vectors are the columns of VSL  and
     VSR,  respectively,  where  VSL  and  VSR are the orthogonal
     matrices which reduce A and B to Schur form:

     Schur form of (A,B) = ( (VSL)**T A (VSR), (VSL)**T B (VSR) )

ARGUMENTS

     JOBVSL (input)
               = 'N':  do not compute the left Schur vectors;
               = 'V':  compute the left Schur vectors.

     JOBVSR (input)
               = 'N':  do not compute the right Schur vectors;
               = 'V':  compute the right Schur vectors.

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

     A (input/output)
               On entry, the first of the pair of matrices  whose
               generalized  eigenvalues  and  (optionally)  Schur
               vectors are to be computed.  On exit, the general-
               ized  Schur  form  of A.  Note: to avoid overflow,
               the Frobenius norm of the matrix A should be  less
               than the overflow threshold.

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

     B (input/output)
               On entry, the second of the pair of matrices whose
               generalized  eigenvalues  and  (optionally)  Schur
               vectors are to be computed.  On exit, the general-
               ized  Schur  form  of B.  Note: to avoid overflow,
               the Frobenius norm of the matrix B should be  less
               than the overflow threshold.

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

     ALPHAR (output)
               On  exit,   (ALPHAR(j)   +   ALPHAI(j)*i)/BETA(j),
               j=1,...,N,  will  be  the generalized eigenvalues.
               ALPHAR(j)   +    ALPHAI(j)*i,    j=1,...,N     and
               BETA(j),j=1,...,N   are  the diagonals of the com-
               plex Schur form (A,B) that would result if the  2-
               by-2  diagonal  blocks  of  the real Schur form of
               (A,B) were  further  reduced  to  triangular  form
               using  2-by-2 complex unitary transformations.  If
               ALPHAI(j) is zero, then  the  j-th  eigenvalue  is
               real;  if  positive,  then  the  j-th and (j+1)-st
               eigenvalues are a  complex  conjugate  pair,  with
               ALPHAI(j+1) negative.

               Note:   the   quotients   ALPHAR(j)/BETA(j)    and
               ALPHAI(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, ALPHAR and  ALPHAI  will  be
               always  less  than  and  usually  comparable  with
               norm(A) in magnitude, and BETA  always  less  than
               and usually comparable with norm(B).

     ALPHAI (output)
               See the description for ALPHAR.

     BETA (output)
               See the description for ALPHAR.

     VSL (input)
               If JOBVSL = 'V', VSL will contain the  left  Schur
               vectors.   (See "Purpose", above.)  Not referenced
               if JOBVSL = 'N'.

     LDVSL (input)
               The leading dimension of  the  matrix  VSL.  LDVSL
               >=1, and if JOBVSL = 'V', LDVSL >= N.

     VSR (input)
               If JOBVSR = 'V', VSR will contain the right  Schur
               vectors.   (See "Purpose", above.)  Not referenced
               if JOBVSR = 'N'.

     LDVSR (input)
               The leading dimension of the matrix VSR. LDVSR  >=
               1, and if JOBVSR = 'V', LDVSR >= N.

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

     LDWORK (input)
               The  dimension  of  the  array  WORK.   LDWORK  >=
               max(1,4*N).   For  good  performance,  LDWORK must
               generally be larger.  To compute the optimal value
               of  LDWORK,  call  ILAENV  to  get blocksizes (for
               SGEQRF, SORMQR, and SORGQR.)  Then compute:  NB --
               MAX  of  the  blocksizes  for  SGEQRF, SORMQR, and
               SORGQR The optimal LDWORK is  2*N + N*(NB+1).

               If LDWORK = -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 LDWORK is issued by XERBLA.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               = 1,...,N:  The QZ iteration  failed.   (A,B)  are
               not  in  Schur form, but ALPHAR(j), ALPHAI(j), and
               BETA(j) should be correct for  j=INFO+1,...,N.   >
               N:  errors that usually indicate LAPACK problems:
               =N+1: error return from SGGBAL
               =N+2: error return from SGEQRF
               =N+3: error return from SORMQR
               =N+4: error return from SORGQR
               =N+5: error return from SGGHRD
               =N+6: error return from SHGEQZ (other than  failed
               iteration) =N+7: error return from SGGBAK (comput-
               ing VSL)
               =N+8: error return from SGGBAK (computing VSR)
               =N+9: error return from SLASCL (various places)