Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgges (3p)

Name

zgges - N complex nonsymmetric matrices (A,B), the generalized eigenvalues, the generalized complex Schur form (S, T), and optionally left and/or right Schur vectors (VSL and VSR)

Synopsis

SUBROUTINE ZGGES(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B, LDB,
SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK, RWORK,
BWORK, INFO)

CHARACTER*1 JOBVSL, JOBVSR, SORT
DOUBLE  COMPLEX  A(LDA,*),  B(LDB,*),  ALPHA(*), BETA(*), VSL(LDVSL,*),
VSR(LDVSR,*), WORK(*)
INTEGER N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
LOGICAL DELCTG
LOGICAL BWORK(*)
DOUBLE PRECISION RWORK(*)

SUBROUTINE ZGGES_64(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B, LDB,
SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK, RWORK,
BWORK, INFO)

CHARACTER*1 JOBVSL, JOBVSR, SORT
DOUBLE COMPLEX A(LDA,*),  B(LDB,*),  ALPHA(*),  BETA(*),  VSL(LDVSL,*),
VSR(LDVSR,*), WORK(*)
INTEGER*8 N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
LOGICAL*8 DELCTG
LOGICAL*8 BWORK(*)
DOUBLE PRECISION RWORK(*)




F95 INTERFACE
SUBROUTINE GGES(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B, LDB,
SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK,
RWORK, BWORK, INFO)

CHARACTER(LEN=1) :: JOBVSL, JOBVSR, SORT
COMPLEX(8), DIMENSION(:) :: ALPHA, BETA, WORK
COMPLEX(8), DIMENSION(:,:) :: A, B, VSL, VSR
INTEGER :: N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
LOGICAL :: DELCTG
LOGICAL, DIMENSION(:) :: BWORK
REAL(8), DIMENSION(:) :: RWORK

SUBROUTINE GGES_64(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B,
LDB, SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK,
LWORK, RWORK, BWORK, INFO)

CHARACTER(LEN=1) :: JOBVSL, JOBVSR, SORT
COMPLEX(8), DIMENSION(:) :: ALPHA, BETA, WORK
COMPLEX(8), DIMENSION(:,:) :: A, B, VSL, VSR
INTEGER(8) :: N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
LOGICAL(8) :: DELCTG
LOGICAL(8), DIMENSION(:) :: BWORK
REAL(8), DIMENSION(:) :: RWORK




C INTERFACE
#include <sunperf.h>

void zgges(char jobvsl, char jobvsr, char sort, int(*delztg)(doublecom-
plex,doublecomplex), int n, doublecomplex *a, int  lda,  dou-
blecomplex *b, int ldb, int *sdim, doublecomplex *alpha, dou-
blecomplex *beta, doublecomplex *vsl, int  ldvsl,  doublecom-
plex *vsr, int ldvsr, int *info);

void  zgges_64(char  jobvsl, char jobvsr, char sort, long(*delztg)(dou-
blecomplex,doublecomplex), long  n,  doublecomplex  *a,  long
lda,  doublecomplex  *b,  long ldb, long *sdim, doublecomplex
*alpha, doublecomplex *beta, doublecomplex *vsl, long  ldvsl,
doublecomplex *vsr, long ldvsr, long *info);

Description

Oracle Solaris Studio Performance Library                            zgges(3P)



NAME
       zgges  -  compute  for  a  pair of N-by-N complex nonsymmetric matrices
       (A,B), the generalized eigenvalues, the generalized complex Schur  form
       (S, T), and optionally left and/or right Schur vectors (VSL and VSR)


SYNOPSIS
       SUBROUTINE ZGGES(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B, LDB,
             SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK, RWORK,
             BWORK, INFO)

       CHARACTER*1 JOBVSL, JOBVSR, SORT
       DOUBLE  COMPLEX  A(LDA,*),  B(LDB,*),  ALPHA(*), BETA(*), VSL(LDVSL,*),
       VSR(LDVSR,*), WORK(*)
       INTEGER N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
       LOGICAL DELCTG
       LOGICAL BWORK(*)
       DOUBLE PRECISION RWORK(*)

       SUBROUTINE ZGGES_64(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B, LDB,
             SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK, RWORK,
             BWORK, INFO)

       CHARACTER*1 JOBVSL, JOBVSR, SORT
       DOUBLE COMPLEX A(LDA,*),  B(LDB,*),  ALPHA(*),  BETA(*),  VSL(LDVSL,*),
       VSR(LDVSR,*), WORK(*)
       INTEGER*8 N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
       LOGICAL*8 DELCTG
       LOGICAL*8 BWORK(*)
       DOUBLE PRECISION RWORK(*)




   F95 INTERFACE
       SUBROUTINE GGES(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B, LDB,
              SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK,
              RWORK, BWORK, INFO)

       CHARACTER(LEN=1) :: JOBVSL, JOBVSR, SORT
       COMPLEX(8), DIMENSION(:) :: ALPHA, BETA, WORK
       COMPLEX(8), DIMENSION(:,:) :: A, B, VSL, VSR
       INTEGER :: N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
       LOGICAL :: DELCTG
       LOGICAL, DIMENSION(:) :: BWORK
       REAL(8), DIMENSION(:) :: RWORK

       SUBROUTINE GGES_64(JOBVSL, JOBVSR, SORT, DELCTG, N, A, LDA, B,
              LDB, SDIM, ALPHA, BETA, VSL, LDVSL, VSR, LDVSR, WORK,
              LWORK, RWORK, BWORK, INFO)

       CHARACTER(LEN=1) :: JOBVSL, JOBVSR, SORT
       COMPLEX(8), DIMENSION(:) :: ALPHA, BETA, WORK
       COMPLEX(8), DIMENSION(:,:) :: A, B, VSL, VSR
       INTEGER(8) :: N, LDA, LDB, SDIM, LDVSL, LDVSR, LWORK, INFO
       LOGICAL(8) :: DELCTG
       LOGICAL(8), DIMENSION(:) :: BWORK
       REAL(8), DIMENSION(:) :: RWORK




   C INTERFACE
       #include <sunperf.h>

       void zgges(char jobvsl, char jobvsr, char sort, int(*delztg)(doublecom-
                 plex,doublecomplex), int n, doublecomplex *a, int  lda,  dou-
                 blecomplex *b, int ldb, int *sdim, doublecomplex *alpha, dou-
                 blecomplex *beta, doublecomplex *vsl, int  ldvsl,  doublecom-
                 plex *vsr, int ldvsr, int *info);

       void  zgges_64(char  jobvsl, char jobvsr, char sort, long(*delztg)(dou-
                 blecomplex,doublecomplex), long  n,  doublecomplex  *a,  long
                 lda,  doublecomplex  *b,  long ldb, long *sdim, doublecomplex
                 *alpha, doublecomplex *beta, doublecomplex *vsl, long  ldvsl,
                 doublecomplex *vsr, long ldvsr, long *info);



PURPOSE
       zgges  computes  for  a  pair  of  N-by-N complex nonsymmetric matrices
       (A,B), the generalized eigenvalues, the generalized complex Schur  form
       (S,  T),  and optionally left and/or right Schur vectors (VSL and VSR).
       This gives the generalized Schur factorization

               (A,B) = ( (VSL)*S*(VSR)**H, (VSL)*T*(VSR)**H )

       where (VSR)**H is the conjugate-transpose of VSR.

       Optionally, it also orders the eigenvalues so that a  selected  cluster
       of eigenvalues appears in the leading diagonal blocks of the upper tri-
       angular matrix S and the upper triangular matrix T. The leading columns
       of  VSL  and  VSR then form an unitary basis for the corresponding left
       and right eigenspaces (deflating subspaces).

       (If only the generalized eigenvalues are needed, use the  driver  ZGGEV
       instead, which is faster.)

       A  generalized eigenvalue for a pair of matrices (A,B) is 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 inter-
       pretation for beta=0, and even for both being zero.

       A pair of matrices (S,T) is in generalized complex Schur form if S  and
       T are upper triangular and, in addition, the diagonal elements of T are
       non-negative real numbers.


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.


       SORT (input)
                 Specifies whether or not to  order  the  eigenvalues  on  the
                 diagonal  of the generalized Schur form.  = 'N':  Eigenvalues
                 are not ordered;
                 = 'S':  Eigenvalues are ordered (see DELCTG).


       DELCTG (input)
                 LOGICAL FUNCTION of two DOUBLE COMPLEX arguments DELCTG  must
                 be  declared  EXTERNAL  in the calling subroutine.  If SORT =
                 'N', DELCTG is not referenced.  If SORT = 'S', DELCTG is used
                 to  select  eigenvalues  to sort to the top left of the Schur
                 form.   An  eigenvalue  ALPHA(j)/BETA(j)   is   selected   if
                 DELCTG(ALPHA(j),BETA(j)) is true.

                 Note that a selected complex eigenvalue may no longer satisfy
                 DELCTG(ALPHA(j),BETA(j))  =  .TRUE.  after  ordering,   since
                 ordering  may  change the value of complex eigenvalues (espe-
                 cially if the eigenvalue is ill-conditioned),  in  this  case
                 INFO is set to N+2 (See INFO below).


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


       A (input/output)
                 DOUBLE  COMPLEX  array, dimension(LDA, N) On entry, the first
                 of the pair of matrices.  On exit, A has been overwritten  by
                 its generalized Schur form S.


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


       B (input/output)
                 DOUBLE  COMPLEX  array, dimension(LDB,N) On entry, the second
                 of the pair of matrices.  On exit, B has been overwritten  by
                 its generalized Schur form T.


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


       SDIM (output)
                 If SORT = 'N', SDIM = 0.  If SORT = 'S', SDIM = number of ei-
                 genvalues (after sorting) for which DELCTG is true.


       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 ZGGES. 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 description of ALPHA.


       VSL (output)
                 DOUBLE COMPLEX array, dimension(LDVSL, N) If  JOBVSL  =  'V',
                 VSL  will  contain the left Schur vectors.  Not referenced if
                 JOBVSL = 'N'.


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


       VSR (output)
                 DOUBLE COMPLEX array, dimension(LDVSR,N) If JOBVSR = 'V', VSR
                 will contain the right Schur vectors.  Not referenced if JOB-
                 VSR = 'N'.


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


       WORK (workspace)
                 DOUBLE COMPLEX array, dimension(LWORK) 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 generally 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)
                 DOUBLE PRECISION array, dimension(8*N)

       BWORK (workspace)
                 LOGICAL array, dimension(N) Not referenced if SORT = '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:  =N+1: other than QZ iteration failed
                 in ZHGEQZ
                 =N+2: after reordering, roundoff changed values of some  com-
                 plex  eigenvalues so that leading eigenvalues in the General-
                 ized Schur form no longer satisfy DELCTG=.TRUE.   This  could
                 also  be  caused  due to scaling.  =N+3: reordering falied in
                 ZTGSEN.




                                  7 Nov 2015                         zgges(3P)