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, complex *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 unitary 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)* (in) B(in) Z(in)* = Q(out) B(out) Z(out)*

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


ARGUMENTS


FURTHER DETAILS

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