Contents


NAME

     chbgst - reduce a complex Hermitian-definite banded general-
     ized  eigenproblem  A*x  = lambda*B*x to standard form C*y =
     lambda*y,

SYNOPSIS

     SUBROUTINE CHBGST(VECT, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, X, LDX,
           WORK, RWORK, INFO)

     CHARACTER * 1 VECT, UPLO
     COMPLEX AB(LDAB,*), BB(LDBB,*), X(LDX,*), WORK(*)
     INTEGER N, KA, KB, LDAB, LDBB, LDX, INFO
     REAL RWORK(*)

     SUBROUTINE CHBGST_64(VECT, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, X,
           LDX, WORK, RWORK, INFO)

     CHARACTER * 1 VECT, UPLO
     COMPLEX AB(LDAB,*), BB(LDBB,*), X(LDX,*), WORK(*)
     INTEGER*8 N, KA, KB, LDAB, LDBB, LDX, INFO
     REAL RWORK(*)

  F95 INTERFACE
     SUBROUTINE HBGST(VECT, UPLO, [N], KA, KB, AB, [LDAB], BB, [LDBB], X,
            [LDX], [WORK], [RWORK], [INFO])

     CHARACTER(LEN=1) :: VECT, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: AB, BB, X
     INTEGER :: N, KA, KB, LDAB, LDBB, LDX, INFO
     REAL, DIMENSION(:) :: RWORK

     SUBROUTINE HBGST_64(VECT, UPLO, [N], KA, KB, AB, [LDAB], BB, [LDBB],
            X, [LDX], [WORK], [RWORK], [INFO])

     CHARACTER(LEN=1) :: VECT, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: AB, BB, X
     INTEGER(8) :: N, KA, KB, LDAB, LDBB, LDX, INFO
     REAL, DIMENSION(:) :: RWORK

  C INTERFACE
     #include <sunperf.h>

     void chbgst(char vect, char uplo, int n,  int  ka,  int  kb,
               complex *ab, int ldab, complex *bb, int ldbb, com-
               plex *x, int ldx, int *info);
     void chbgst_64(char vect, char uplo, long n, long  ka,  long
               kb,  complex  *ab,  long  ldab,  complex *bb, long
               ldbb, complex *x, long ldx, long *info);

PURPOSE

     chbgst reduces a complex Hermitian-definite banded  general-
     ized eigenproblem  A*x = lambda*B*x  to standard form  C*y =
     lambda*y, such that C has the same bandwidth as A.

     B must have been previously factorized as S**H*S by  CPBSTF,
     using  a split Cholesky factorization. A is overwritten by C
     = X**H*A*X, where X = S**(-1)*Q and Q is  a  unitary  matrix
     chosen to preserve the bandwidth of A.

ARGUMENTS

     VECT (input)
               = 'N':  do not form the transformation matrix X;
               = 'V':  form X.

     UPLO (input)
               = 'U':  Upper triangle of A is stored;
               = 'L':  Lower triangle of A is stored.

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

     KA (input)
               The number of superdiagonals of the  matrix  A  if
               UPLO  = 'U', or the number of subdiagonals if UPLO
               = 'L'.  KA >= 0.

     KB (input)
               The number of superdiagonals of the  matrix  B  if
               UPLO  = 'U', or the number of subdiagonals if UPLO
               = 'L'.  KA >= KB >= 0.

     AB (input/output)
               On entry, the upper or lower triangle of the  Her-
               mitian  band  matrix  A,  stored in the first ka+1
               rows of the array.  The j-th column of A is stored
               in the j-th column of the array AB as follows:  if
               UPLO = 'U', AB(ka+1+i-j,j) = A(i,j)  for  max(1,j-
               ka)<=i<=j;  if UPLO = 'L', AB(1+i-j,j)    = A(i,j)
               for j<=i<=min(n,j+ka).
               On exit, the transformed matrix  X**H*A*X,  stored
               in the same format as A.

     LDAB (input)
               The leading dimension of the array  AB.   LDAB  >=
               KA+1.

     BB (input)
               The banded factor S from the split  Cholesky  fac-
               torization  of B, as returned by CPBSTF, stored in
               the first kb+1 rows of the array.

     LDBB (input)
               The leading dimension of the array  BB.   LDBB  >=
               KB+1.

     X (output)
               If VECT = 'V', the n-by-n matrix  X.   If  VECT  =
               'N', the array X is not referenced.

     LDX (input)
               The leading dimension of  the  array  X.   LDX  >=
               max(1,N) if VECT = 'V'; LDX >= 1 otherwise.

     WORK (workspace)
               dimension(N)

     RWORK (workspace)
               dimension(N)

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