Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgegs (3p)

Name

cgegs - routine is deprecated and has been replaced by routine CGGES

Synopsis

SUBROUTINE CGEGS(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA, BETA, VSL,
LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2, INFO)

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

SUBROUTINE CGEGS_64(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA, BETA,
VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2, INFO)

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




F95 INTERFACE
SUBROUTINE GEGS(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA, BETA,
VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2, INFO)

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

SUBROUTINE GEGS_64(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA,
BETA, VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2,
INFO)

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




C INTERFACE
#include <sunperf.h>

void  cgegs(char  jobvsl, char jobvsr, int n, complex *a, int lda, com-
plex *b, int ldb,  complex  *alpha,  complex  *beta,  complex
*vsl, int ldvsl, complex *vsr, int ldvsr, int *info);

void  cgegs_64(char  jobvsl, char jobvsr, long n, complex *a, long lda,
complex *b, long ldb, complex *alpha, complex *beta,  complex
*vsl, long ldvsl, complex *vsr, long ldvsr, long *info);

Description

Oracle Solaris Studio Performance Library                            cgegs(3P)



NAME
       cgegs - routine is deprecated and has been replaced by routine CGGES


SYNOPSIS
       SUBROUTINE CGEGS(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA, BETA, VSL,
             LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2, INFO)

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

       SUBROUTINE CGEGS_64(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA, BETA,
             VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2, INFO)

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




   F95 INTERFACE
       SUBROUTINE GEGS(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA, BETA,
              VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2, INFO)

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

       SUBROUTINE GEGS_64(JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHA,
              BETA, VSL, LDVSL, VSR, LDVSR, WORK, LDWORK, WORK2,
              INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void  cgegs(char  jobvsl, char jobvsr, int n, complex *a, int lda, com-
                 plex *b, int ldb,  complex  *alpha,  complex  *beta,  complex
                 *vsl, int ldvsl, complex *vsr, int ldvsr, int *info);

       void  cgegs_64(char  jobvsl, char jobvsr, long n, complex *a, long lda,
                 complex *b, long ldb, complex *alpha, complex *beta,  complex
                 *vsl, long ldvsl, complex *vsr, long ldvsr, long *info);



PURPOSE
       cgegs routine is deprecated and has been replaced by routine CGGES.

       CGEGS computes for a pair of N-by-N complex nonsymmetric matrices A, B:
       the generalized eigenvalues (alpha, beta), the complex 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 CGEGV
       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  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)

       The  (generalized)  Schur  form  of a pair of matrices is the result of
       multiplying both matrices on the left by one unitary matrix and both on
       the  right  by another unitary matrix, these two unitary matrices being
       chosen so as to bring the pair of matrices into upper  triangular  form
       with  the  diagonal elements of B being non-negative real numbers (this
       is also called complex Schur form.)

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

       Schur form of (A,B) = ( (VSL)**H A (VSR), (VSL)**H 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  com-
                 puted.  On exit, the generalized Schur form of A.


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


       B (input/output)
                 On  entry,  the second of the pair of matrices whose general-
                 ized eigenvalues and (optionally) Schur  vectors  are  to  be
                 computed.  On exit, the generalized Schur form of B.


       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 general-
                 ized  eigenvalues.   ALPHA(j),   j=1,...,N    and    BETA(j),
                 j=1,...,N   are the diagonals of the complex Schur form (A,B)
                 output by CGEGS.  The  BETA(j) will be non-negative real.

                 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.   How-
                 ever,  ALPHA  will be always less than and usually comparable
                 with norm(A) in magnitude, and BETA always less than and usu-
                 ally comparable with norm(B).


       BETA (output)
                 See the description of ALPHA.


       VSL (output)
                 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 (output)
                 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,2*N).  For
                 good performance, LDWORK must generally be larger.   To  com-
                 pute  the  optimal value of LDWORK, call ILAENV to get block-
                 sizes (for CGEQRF, CUNMQR, and CUNGQR.)  Then compute: NB  as
                 the MAX of the blocksizes for CGEQRF, CUNMQR, and CUNGQR; the
                 optimal LDWORK is N*(NB+1).

                 If LDWORK = -1, then a workspace query is assumed;  the  rou-
                 tine  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.


       WORK2 (workspace)
                 dimension(3*N)


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value.
                 =1,...,N:  The  QZ  iteration failed.  (A,B) are not in Schur
                 form,  but  ALPHA(j)  and  BETA(j)  should  be  correct   for
                 j=INFO+1,...,N.   >  N:   errors that usually indicate LAPACK
                 problems:
                 =N+1: error return from CGGBAL
                 =N+2: error return from CGEQRF
                 =N+3: error return from CUNMQR
                 =N+4: error return from CUNGQR
                 =N+5: error return from CGGHRD
                 =N+6: error return from CHGEQZ (other than failed  iteration)
                 =N+7: error return from CGGBAK (computing VSL)
                 =N+8: error return from CGGBAK (computing VSR)
                 =N+9: error return from CLASCL (various places)




                                  7 Nov 2015                         cgegs(3P)