Contents


NAME

     chgeqz - implement a single-shift version of the  QZ  method
     for       finding      the      generalized      eigenvalues
     w(i)=ALPHA(i)/BETA(i) of the equation   det( A-w(i) B ) =  0
     If JOB='S', then the pair (A,B) is simultaneously reduced to
     Schur form (i.e., A and B  are  both  upper  triangular)  by
     applying one unitary tranformation (usually called Q) on the
     left and another (usually called Z) on the right

SYNOPSIS

     SUBROUTINE CHGEQZ(JOB, COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB,
           ALPHA, BETA, Q, LDQ, Z, LDZ, WORK, LWORK, RWORK, INFO)

     CHARACTER * 1 JOB, COMPQ, COMPZ
     COMPLEX A(LDA,*),  B(LDB,*),  ALPHA(*),  BETA(*),  Q(LDQ,*),
     Z(LDZ,*), WORK(*)
     INTEGER N, ILO, IHI, LDA, LDB, LDQ, LDZ, LWORK, INFO
     REAL RWORK(*)

     SUBROUTINE CHGEQZ_64(JOB, COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB,
           ALPHA, BETA, Q, LDQ, Z, LDZ, WORK, LWORK, RWORK, INFO)

     CHARACTER * 1 JOB, COMPQ, COMPZ
     COMPLEX A(LDA,*),  B(LDB,*),  ALPHA(*),  BETA(*),  Q(LDQ,*),
     Z(LDZ,*), WORK(*)
     INTEGER*8 N, ILO, IHI, LDA, LDB, LDQ, LDZ, LWORK, INFO
     REAL RWORK(*)

  F95 INTERFACE
     SUBROUTINE HGEQZ(JOB, COMPQ, COMPZ, [N], ILO, IHI, A, [LDA], B, [LDB],
            ALPHA, BETA, Q, [LDQ], Z, [LDZ], [WORK], [LWORK], [RWORK], [INFO])

     CHARACTER(LEN=1) :: JOB, COMPQ, COMPZ
     COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK
     COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
     INTEGER :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, LWORK, INFO
     REAL, DIMENSION(:) :: RWORK

     SUBROUTINE HGEQZ_64(JOB, COMPQ, COMPZ, [N], ILO, IHI, A, [LDA], B,
            [LDB], ALPHA, BETA, Q, [LDQ], Z, [LDZ], [WORK], [LWORK], [RWORK],
            [INFO])

     CHARACTER(LEN=1) :: JOB, COMPQ, COMPZ
     COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK
     COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
     INTEGER(8) :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, LWORK, INFO
     REAL, DIMENSION(:) :: RWORK
  C INTERFACE
     #include <sunperf.h>

     void chgeqz(char job, char compq, char  compz,  int  n,  int
               ilo, int ihi, complex *a, int lda, complex *b, int
               ldb, complex *alpha, complex  *beta,  complex  *q,
               int ldq, complex *z, int ldz, int *info);

     void chgeqz_64(char job, char compq,  char  compz,  long  n,
               long  ilo, long ihi, complex *a, long lda, complex
               *b, long ldb, complex *alpha, complex *beta,  com-
               plex  *q,  long  ldq,  complex  *z, long ldz, long
               *info);

PURPOSE

     chgeqz implements a single-shift version of  the  QZ  method
     for       finding      the      generalized      eigenvalues
     w(i)=ALPHA(i)/BETA(i)   of   the   equation   A   are   then
     ALPHA(1),...,ALPHA(N), and of B are BETA(1),...,BETA(N).

     If JOB='S' and COMPQ and COMPZ are 'V' or 'I', then the uni-
     tary  transformations  used  to reduce (A,B) are accumulated
     into the arrays Q and Z s.t.:
     (in) A(in) Z(in)* = Q(out) A(out) Z(out)*

     Ref: C.B. Moler & G.W. Stewart, "An Algorithm  for  General-
     ized   Matrixigenvalue  Problems",  SIAM  J.  Numer.  Anal.,
     10(1973),p. 241--256.

ARGUMENTS

     JOB (input)
               = 'E': compute only ALPHA and BETA.  A and B  will
               not  necessarily  be  put  into  generalized Schur
               form.  = 'S': put A and B into  generalized  Schur
               form, as well as computing ALPHA and BETA.

     COMPQ (input)
               = 'N': do not modify Q.
               = 'V': multiply the array Q on the  right  by  the
               conjugate  transpose  of the unitary tranformation
               that is applied to the left side of  A  and  B  to
               reduce them to Schur form.  = 'I': like COMPQ='V',
               except that Q will be initialized to the  identity
               first.

     COMPZ (input)
               = 'N': do not modify Z.
               = 'V': multiply the array Z on the  right  by  the
               unitary tranformation that is applied to the right
               side of A and B to reduce them to Schur  form.   =
               'I':  like  COMPZ='V',  except that Z will be ini-
               tialized to the identity first.

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

     ILO (input)
               It is assumed that A is already  upper  triangular
               in rows and columns 1:ILO-1 and IHI+1:N.  1 <= ILO
               <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.

     IHI (input)
               It is assumed that A is already  upper  triangular
               in rows and columns 1:ILO-1 and IHI+1:N.  1 <= ILO
               <= IHI <= N, if N > 0; ILO=1 and IHI=0, if N=0.

     A (input) On entry, the N-by-N upper  Hessenberg  matrix  A.
               Elements  below  the subdiagonal must be zero.  If
               JOB='S', then on exit  A  and  B  will  have  been
               simultaneously  reduced  to upper triangular form.
               If JOB='E', then on exit A  will  have  been  des-
               troyed.

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

     B (input) On entry, the N-by-N upper  triangular  matrix  B.
               Elements  below  the  diagonal  must  be zero.  If
               JOB='S', then on exit  A  and  B  will  have  been
               simultaneously  reduced  to upper triangular form.
               If JOB='E', then on exit B  will  have  been  des-
               troyed.

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

     ALPHA (output)
               The diagonal elements of A when the pair (A,B) has
               been  reduced  to  Schur  form.   ALPHA(i)/BETA(i)
               i=1,...,N are the generalized eigenvalues.
     BETA (output)
               The diagonal elements of B when the pair (A,B) has
               been  reduced  to  Schur  form.   ALPHA(i)/BETA(i)
               i=1,...,N are the generalized eigenvalues.  A  and
               B  are  normalized so that BETA(1),...,BETA(N) are
               non-negative real numbers.

     Q (input/output)
               If COMPQ='N', then Q will not be  referenced.   If
               COMPQ='V'  or 'I', then the conjugate transpose of
               the unitary transformations which are applied to A
               and  B  on the left will be applied to the array Q
               on the right.

     LDQ (input)
               The leading dimension of the array Q.  LDQ  >=  1.
               If COMPQ='V' or 'I', then LDQ >= N.

     Z (input/output)
               If COMPZ='N', then Z will not be  referenced.   If
               COMPZ='V' or 'I', then the unitary transformations
               which are applied to A and B on the right will  be
               applied to the array Z on the right.

     LDZ (input)
               The leading dimension of the array Z.  LDZ  >=  1.
               If COMPZ='V' or 'I', then LDZ >= 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,N).

               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(N)
     INFO (output)
               = 0: successful exit
               < 0: if INFO = -i, the i-th argument had an  ille-
               gal value
               = 1,...,N: the  QZ  iteration  did  not  converge.
               (A,B)  is  not  in  Schur  form,  but ALPHA(i) and
               BETA(i),  i=INFO+1,...,N  should  be  correct.   =
               N+1,...,2*N:  the shift calculation failed.  (A,B)
               is not in Schur form, but  ALPHA(i)  and  BETA(i),
               i=INFO-N+1,...,N   should   be  correct.   >  2*N:
               various "impossible" errors.

FURTHER DETAILS

     We assume that complex ABS works as long  as  its  value  is
     less than overflow.