Contents


NAME

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

SYNOPSIS

     SUBROUTINE CHEGVD(ITYPE, JOBZ, UPLO, N, A, LDA, B, LDB, W, WORK,
           LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     COMPLEX A(LDA,*), B(LDB,*), WORK(*)
     INTEGER ITYPE, N, LDA, LDB, LWORK, LRWORK, LIWORK, INFO
     INTEGER IWORK(*)
     REAL W(*), RWORK(*)

     SUBROUTINE CHEGVD_64(ITYPE, JOBZ, UPLO, N, A, LDA, B, LDB, W, WORK,
           LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     COMPLEX A(LDA,*), B(LDB,*), WORK(*)
     INTEGER*8 ITYPE, N, LDA, LDB, LWORK, LRWORK, LIWORK, INFO
     INTEGER*8 IWORK(*)
     REAL W(*), RWORK(*)

  F95 INTERFACE
     SUBROUTINE HEGVD(ITYPE, JOBZ, UPLO, [N], A, [LDA], B, [LDB], W, [WORK],
            [LWORK], [RWORK], [LRWORK], [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, B
     INTEGER :: ITYPE, N, LDA, LDB, LWORK, LRWORK, LIWORK, INFO
     INTEGER, DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: W, RWORK

     SUBROUTINE HEGVD_64(ITYPE, JOBZ, UPLO, [N], A, [LDA], B, [LDB], W,
            [WORK], [LWORK], [RWORK], [LRWORK], [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A, B
     INTEGER(8) :: ITYPE, N, LDA,  LDB,  LWORK,  LRWORK,  LIWORK,
     INFO
     INTEGER(8), DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: W, RWORK
  C INTERFACE
     #include <sunperf.h>

     void chegvd(int itype, char jobz, char uplo, int n,  complex
               *a,  int  lda,  complex *b, int ldb, float *w, int
               *info);

     void chegvd_64(long itype, char jobz,  char  uplo,  long  n,
               complex  *a, long lda, complex *b, long ldb, float
               *w, long *info);

PURPOSE

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

     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

     ITYPE (input)
               Specifies the problem type to be solved:
               = 1:  A*x = (lambda)*B*x
               = 2:  A*B*x = (lambda)*x
               = 3:  B*A*x = (lambda)*x

     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.
     A (input/output)
               On entry, the Hermitian matrix A.  If UPLO =  'U',
               the leading N-by-N upper triangular part of A con-
               tains the upper triangular part of the  matrix  A.
               If UPLO = 'L', the leading N-by-N lower triangular
               part of A contains the lower  triangular  part  of
               the matrix A.

               On exit, if JOBZ = 'V', then if INFO = 0,  A  con-
               tains the matrix Z of eigenvectors.  The eigenvec-
               tors are normalized as follows:  if ITYPE =  1  or
               2,  Z**H*B*Z = I; if ITYPE = 3, Z**H*inv(B)*Z = I.
               If JOBZ = 'N', then on exit the upper triangle (if
               UPLO='U')  or  the lower triangle (if UPLO='L') of
               A, including the diagonal, is destroyed.

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

     B (input/output)
               On entry, the Hermitian matrix B.  If UPLO =  'U',
               the leading N-by-N upper triangular part of B con-
               tains the upper triangular part of the  matrix  B.
               If UPLO = 'L', the leading N-by-N lower triangular
               part of B contains the lower  triangular  part  of
               the matrix B.

               On exit, if INFO <= N, the part  of  B  containing
               the matrix is overwritten by the triangular factor
               U or L from the Cholesky factorization B =  U**H*U
               or B = L*L**H.

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

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

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

     LWORK (input)
               The  length  of  the  array  WORK.   If  N  <=  1,
               LWORK  >= 1.  If JOBZ  = 'N' and N > 1, LWORK >= N
               + 1.  If JOBZ  = 'V' and N > 1,  LWORK  >=  2*N  +
               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 the 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 the array  IWORK.   If  N  <=  1,
               LIWORK  >= 1.  If JOBZ  = 'N' and N > 1, LIWORK >=
               1.  If JOBZ  = 'V' and N > 1, LIWORK >= 3 + 5*N.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value
               > 0:  CPOTRF or CHEEVD returned an error code:
               <= N:  if INFO = i, CHEEVD failed to  converge;  i
               off-diagonal elements of an intermediate tridiago-
               nal form did not converge to zero; > N:   if  INFO
               =  N  + i, for 1 <= i <= N, then the leading minor
               of order i of 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