Contents


NAME

     cheev - compute all eigenvalues and,  optionally,  eigenvec-
     tors of a complex Hermitian matrix A

SYNOPSIS

     SUBROUTINE CHEEV(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, WORK2, INFO)

     CHARACTER * 1 JOBZ, UPLO
     COMPLEX A(LDA,*), WORK(*)
     INTEGER N, LDA, LDWORK, INFO
     REAL W(*), WORK2(*)

     SUBROUTINE CHEEV_64(JOBZ, UPLO, N, A, LDA, W, WORK, LDWORK, WORK2,
           INFO)

     CHARACTER * 1 JOBZ, UPLO
     COMPLEX A(LDA,*), WORK(*)
     INTEGER*8 N, LDA, LDWORK, INFO
     REAL W(*), WORK2(*)

  F95 INTERFACE
     SUBROUTINE HEEV(JOBZ, UPLO, [N], A, [LDA], W, [WORK], [LDWORK],
            [WORK2], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A
     INTEGER :: N, LDA, LDWORK, INFO
     REAL, DIMENSION(:) :: W, WORK2

     SUBROUTINE HEEV_64(JOBZ, UPLO, [N], A, [LDA], W, [WORK], [LDWORK],
            [WORK2], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: A
     INTEGER(8) :: N, LDA, LDWORK, INFO
     REAL, DIMENSION(:) :: W, WORK2

  C INTERFACE
     #include <sunperf.h>

     void cheev(char jobz, char uplo, int n, complex *a, int lda,
               float *w, int *info);

     void cheev_64(char jobz, char uplo, long n, complex *a, long
               lda, float *w, long *info);

PURPOSE

     cheev computes all eigenvalues and, optionally, eigenvectors
     of a complex Hermitian matrix A.

ARGUMENTS

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

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

     N (input) The order of the matrix A.  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 contains the orthonormal  eigenvectors
               of  the matrix A.  If JOBZ = 'N', then on exit the
               lower triangle (if UPLO='L') or the upper triangle
               (if  UPLO='U')  of  A,  including the diagonal, is
               destroyed.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               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
               LDWORK.

     LDWORK (input)
               The  length  of  the  array   WORK.    LDWORK   >=
               max(1,2*N-1).   For  optimal efficiency, LDWORK >=
               (NB+1)*N, where NB is  the  blocksize  for  CHETRD
               returned by ILAENV.

               If LDWORK = -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 LDWORK is issued by XERBLA.

     WORK2 (workspace)
               dimension(max(1,3*N-2))

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value
               > 0:  if INFO = i, the algorithm  failed  to  con-
               verge;  i off-diagonal elements of an intermediate
               tridiagonal form did not converge to zero.