Contents


NAME

     cgghrd - reduce a pair of complex matrices (A,B) to general-
     ized  upper  Hessenberg  form using unitary transformations,
     where A is a general matrix and B is upper triangular

SYNOPSIS

     SUBROUTINE CGGHRD(COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q, LDQ,
           Z, LDZ, INFO)

     CHARACTER * 1 COMPQ, COMPZ
     COMPLEX A(LDA,*), B(LDB,*), Q(LDQ,*), Z(LDZ,*)
     INTEGER N, ILO, IHI, LDA, LDB, LDQ, LDZ, INFO

     SUBROUTINE CGGHRD_64(COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q,
           LDQ, Z, LDZ, INFO)

     CHARACTER * 1 COMPQ, COMPZ
     COMPLEX A(LDA,*), B(LDB,*), Q(LDQ,*), Z(LDZ,*)
     INTEGER*8 N, ILO, IHI, LDA, LDB, LDQ, LDZ, INFO

  F95 INTERFACE
     SUBROUTINE GGHRD(COMPQ, COMPZ, [N], ILO, IHI, A, [LDA], B, [LDB], Q,
            [LDQ], Z, [LDZ], [INFO])

     CHARACTER(LEN=1) :: COMPQ, COMPZ
     COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
     INTEGER :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, INFO

     SUBROUTINE GGHRD_64(COMPQ, COMPZ, [N], ILO, IHI, A, [LDA], B, [LDB],
            Q, [LDQ], Z, [LDZ], [INFO])

     CHARACTER(LEN=1) :: COMPQ, COMPZ
     COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
     INTEGER(8) :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, INFO

  C INTERFACE
     #include <sunperf.h>

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

     void cgghrd_64(char compq, char compz,  long  n,  long  ilo,
               long  ihi,  complex *a, long lda, complex *b, long
               ldb, complex *q, long ldq, complex *z,  long  ldz,
               long *info);

PURPOSE

     cgghrd reduces a pair of complex matrices (A,B) to  general-
     ized  upper  Hessenberg  form using unitary transformations,
     where A is a general matrix and B is upper triangular:  Q' *
     A * Z = H and Q' * B * Z = T, where H is upper Hessenberg, T
     is upper triangular, and Q and Z are unitary,  and  '  means
     conjugate transpose.

     The unitary matrices Q and Z are determined as  products  of
     Givens  rotations.  They may either be formed explicitly, or
     they may be postmultiplied into input matrices Q1 and Z1, so
     that
     1 * A * Z1' = (Q1*Q) * H * (Z1*Z)'

ARGUMENTS

     COMPQ (input)
               = 'N': do not compute Q;
               = 'I': Q is initialized to the  unit  matrix,  and
               the  unitary  matrix  Q is returned; = 'V': Q must
               contain a unitary matrix Q1 on entry, and the pro-
               duct Q1*Q is returned.

     COMPZ (input)
               = 'N': do not compute Q;
               = 'I': Q is initialized to the  unit  matrix,  and
               the  unitary  matrix  Q is returned; = 'V': Q must
               contain a unitary matrix Q1 on entry, and the pro-
               duct Q1*Q is returned.

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

     ILO (input)
               It is assumed that A is already  upper  triangular
               in  rows and columns 1:ILO-1 and IHI+1:N.  ILO and
               IHI are normally set by a previous call to CGGBAL;
               otherwise  they  should  be set to 1 and N respec-
               tively.  1 <= ILO <= IHI <= N, if N > 0; ILO=1 and
               IHI=0, if N=0.

     IHI (input)
               See description of ILO.

     A (input/output)
               On entry, the N-by-N general matrix to be reduced.
               On   exit,   the  upper  triangle  and  the  first
               subdiagonal of A are overwritten  with  the  upper
               Hessenberg matrix H, and the rest is set to zero.

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

     B (input/output)
               On entry, the N-by-N upper  triangular  matrix  B.
               On  exit,  the upper triangular matrix T = Q' B Z.
               The elements below the diagonal are set to zero.

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

     Q (input/output)
               If COMPQ='N':  Q is not referenced.
               If COMPQ='I':  on entry, Q need not be set, and on
               exit it contains the unitary matrix Q, where Q' is
               the product of the  Givens  transformations  which
               are applied to A and B on the left.  If COMPQ='V':
               on entry, Q must contain a unitary matrix Q1,  and
               on exit this is overwritten by Q1*Q.

     LDQ (input)
               The leading dimension of the array Q.  LDQ >= N if
               COMPQ='V' or 'I'; LDQ >= 1 otherwise.

     Z (input/output)
               If COMPZ='N':  Z is not referenced.
               If COMPZ='I':  on entry, Z need not be set, and on
               exit  it  contains  the unitary matrix Z, which is
               the product of the  Givens  transformations  which
               are   applied  to  A  and  B  on  the  right.   If
               COMPZ='V':  on entry, Z  must  contain  a  unitary
               matrix  Z1,  and  on  exit  this is overwritten by
               Z1*Z.

     LDZ (input)
               The leading dimension of the array Z.  LDZ >= N if
               COMPZ='V' or 'I'; LDZ >= 1 otherwise.

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.

FURTHER DETAILS

     This routine reduces A to Hessenberg  and  B  to  triangular
     form   by   an   unblocked   reduction,   as   described  in
     _Matrix_Computations_, by Golub and van Loan (Johns  Hopkins
     Press).