NAME

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


SYNOPSIS

  SUBROUTINE ZGGHRD( COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q, 
 *      LDQ, Z, LDZ, INFO)
  CHARACTER * 1 COMPQ, COMPZ
  DOUBLE COMPLEX A(LDA,*), B(LDB,*), Q(LDQ,*), Z(LDZ,*)
  INTEGER N, ILO, IHI, LDA, LDB, LDQ, LDZ, INFO
  SUBROUTINE ZGGHRD_64( COMPQ, COMPZ, N, ILO, IHI, A, LDA, B, LDB, Q, 
 *      LDQ, Z, LDZ, INFO)
  CHARACTER * 1 COMPQ, COMPZ
  DOUBLE 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(8), 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(8), DIMENSION(:,:) :: A, B, Q, Z
  INTEGER(8) :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, INFO

C INTERFACE

#include <sunperf.h>

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

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


PURPOSE

zgghrd reduces a pair of complex matrices (A,B) to generalized 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)' 1 * B * Z1' = (Q1*Q) * T * (Z1*Z)'


ARGUMENTS


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).