Contents


NAME

     chbgvd - compute all the eigenvalues,  and  optionally,  the
     eigenvectors  of  a  complex  generalized Hermitian-definite
     banded eigenproblem, of the form A*x=(lambda)*B*x

SYNOPSIS

     SUBROUTINE CHBGVD(JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
           LDZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     COMPLEX AB(LDAB,*), BB(LDBB,*), Z(LDZ,*), WORK(*)
     INTEGER N, KA, KB, LDAB, LDBB, LDZ, LWORK,  LRWORK,  LIWORK,
     INFO
     INTEGER IWORK(*)
     REAL W(*), RWORK(*)

     SUBROUTINE CHBGVD_64(JOBZ, UPLO, N, KA, KB, AB, LDAB, BB, LDBB, W, Z,
           LDZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     COMPLEX AB(LDAB,*), BB(LDBB,*), Z(LDZ,*), WORK(*)
     INTEGER*8 N, KA, KB, LDAB, LDBB, LDZ, LWORK, LRWORK, LIWORK,
     INFO
     INTEGER*8 IWORK(*)
     REAL W(*), RWORK(*)

  F95 INTERFACE
     SUBROUTINE HBGVD(JOBZ, UPLO, [N], KA, KB, AB, [LDAB], BB, [LDBB], W,
            Z, [LDZ], [WORK], [LWORK], [RWORK], [LRWORK], [IWORK], [LIWORK],
            [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: AB, BB, Z
     INTEGER :: N,  KA,  KB,  LDAB,  LDBB,  LDZ,  LWORK,  LRWORK,
     LIWORK, INFO
     INTEGER, DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: W, RWORK

     SUBROUTINE HBGVD_64(JOBZ, UPLO, [N], KA, KB, AB, [LDAB], BB, [LDBB],
            W, Z, [LDZ], [WORK], [LWORK], [RWORK], [LRWORK], [IWORK], [LIWORK],
            [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: AB, BB, Z
     INTEGER(8) :: N, KA, KB, LDAB,  LDBB,  LDZ,  LWORK,  LRWORK,
     LIWORK, INFO
     INTEGER(8), DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: W, RWORK

  C INTERFACE
     #include <sunperf.h>

     void chbgvd(char jobz, char uplo, int n,  int  ka,  int  kb,
               complex  *ab,  int  ldab,  complex  *bb, int ldbb,
               float *w, complex *z, int ldz, int *info);

     void chbgvd_64(char jobz, char uplo, long n, long  ka,  long
               kb,  complex  *ab,  long  ldab,  complex *bb, long
               ldbb, float *w, complex *z, long ldz, long *info);

PURPOSE

     chbgvd computes all the  eigenvalues,  and  optionally,  the
     eigenvectors  of  a  complex  generalized Hermitian-definite
     banded eigenproblem, of the form  A*x=(lambda)*B*x.  Here  A
     and  B are assumed to be Hermitian and banded, and B is also
     positive definite.  If eigenvectors are desired, it  uses  a
     divide and conquer algorithm.

     The divide and conquer algorithm makes very mild assumptions
     about  floating  point  arithmetic. It will work on machines
     with a guard digit  in  add/subtract,  or  on  those  binary
     machines  without  guard digits which subtract like the Cray
     X-MP, Cray Y-MP, Cray C-90, or Cray-2. It could  conceivably
     fail  on  hexadecimal  or  decimal  machines  without  guard
     digits, but we know of none.

ARGUMENTS

     JOBZ (input)
               = 'N':  Compute eigenvalues only;
               = 'V':  Compute eigenvalues and eigenvectors.

     UPLO (input)
               = 'U':  Upper triangles of A and B are stored;
               = 'L':  Lower triangles of A and B are 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'. 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 contents of AB are destroyed.

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

     BB (input/output)
               On entry, the upper or lower triangle of the  Her-
               mitian  band  matrix  B,  stored in the first kb+1
               rows of the array.  The j-th column of B is stored
               in the j-th column of the array BB as follows:  if
               UPLO = 'U', BB(kb+1+i-j,j) = B(i,j)  for  max(1,j-
               kb)<=i<=j;  if UPLO = 'L', BB(1+i-j,j)    = B(i,j)
               for j<=i<=min(n,j+kb).

               On exit, the factor S from the split Cholesky fac-
               torization B = S**H*S, as returned by CPBSTF.

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

     W (output)
               If INFO = 0, the eigenvalues in ascending order.

     Z (input) If JOBZ = 'V', then if INFO = 0,  Z  contains  the
               matrix  Z of eigenvectors, with the i-th column of
               Z holding the eigenvector  associated  with  W(i).
               The eigenvectors are normalized so that Z**H*B*Z =
               I.  If JOBZ = 'N', then Z is not referenced.
     LDZ (input)
               The leading dimension of the array Z.  LDZ  >=  1,
               and if JOBZ = 'V', LDZ >= N.

     WORK (workspace)
               On exit, if INFO=0, WORK(1)  returns  the  optimal
               LWORK.

     LWORK (input)
               The dimension of the  array  WORK.   If  N  <=  1,
               LWORK  >= 1.  If JOBZ = 'N' and N > 1, LWORK >= N.
               If JOBZ = 'V' and N > 1, LWORK >= 2*N**2.

               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)
               On exit, if INFO=0, RWORK(1) returns  the  optimal
               LRWORK.

     LRWORK (input)
               The  dimension  of  array  RWORK.   If  N  <=   1,
               LRWORK  >=  1.  If JOBZ = 'N' and N > 1, LRWORK >=
               N.  If JOBZ = 'V' and N > 1, LRWORK >= 1 +  5*N  +
               2*N**2.

               If LRWORK = -1, then a workspace query is assumed;
               the  routine  only  calculates the optimal size of
               the RWORK array, returns this value as  the  first
               entry  of  the  RWORK  array, and no error message
               related to LRWORK is issued by XERBLA.

     IWORK (workspace/output)
               On exit, if INFO=0, IWORK(1) returns  the  optimal
               LIWORK.

     LIWORK (input)
               The dimension of array IWORK.  If JOBZ = 'N' or  N
               <=  1,  LIWORK  >=  1.   If  JOBZ = 'V' and N > 1,
               LIWORK >= 3 + 5*N.

               If LIWORK = -1, then a workspace query is assumed;
               the  routine  only  calculates the optimal size of
               the IWORK array, returns this value as  the  first
               entry  of  the  IWORK  array, and no error message
               related to LIWORK is issued by XERBLA.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value
               > 0:  if INFO = i, and i is:
               <= N:  the algorithm failed to converge:   i  off-
               diagonal  elements  of an intermediate tridiagonal
               form did not converge to zero; > N:   if INFO =  N
               + i, for 1 <= i <= N, then CPBSTF
               returned INFO = i: B  is  not  positive  definite.
               The  factorization of B could not be completed and
               no eigenvalues or eigenvectors were computed.

FURTHER DETAILS

     Based on contributions by
        Mark Fahey, Department of Mathematics, Univ. of Kentucky,
     USA