Contents


NAME

     cstedc - compute all eigenvalues and, optionally,  eigenvec-
     tors  of a symmetric tridiagonal matrix using the divide and
     conquer method

SYNOPSIS

     SUBROUTINE CSTEDC(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, RWORK, LRWORK,
           IWORK, LIWORK, INFO)

     CHARACTER * 1 COMPZ
     COMPLEX Z(LDZ,*), WORK(*)
     INTEGER N, LDZ, LWORK, LRWORK, LIWORK, INFO
     INTEGER IWORK(*)
     REAL D(*), E(*), RWORK(*)

     SUBROUTINE CSTEDC_64(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, RWORK,
           LRWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 COMPZ
     COMPLEX Z(LDZ,*), WORK(*)
     INTEGER*8 N, LDZ, LWORK, LRWORK, LIWORK, INFO
     INTEGER*8 IWORK(*)
     REAL D(*), E(*), RWORK(*)

  F95 INTERFACE
     SUBROUTINE STEDC(COMPZ, [N], D, E, Z, [LDZ], [WORK], [LWORK], [RWORK],
            [LRWORK], [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: COMPZ
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: Z
     INTEGER :: N, LDZ, LWORK, LRWORK, LIWORK, INFO
     INTEGER, DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: D, E, RWORK

     SUBROUTINE STEDC_64(COMPZ, [N], D, E, Z, [LDZ], [WORK], [LWORK],
            [RWORK], [LRWORK], [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: COMPZ
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: Z
     INTEGER(8) :: N, LDZ, LWORK, LRWORK, LIWORK, INFO
     INTEGER(8), DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: D, E, RWORK

  C INTERFACE
     #include <sunperf.h>
     void cstedc(char compz, int n, float *d, float  *e,  complex
               *z, int ldz, int *info);

     void cstedc_64(char compz, long n, float *d, float *e,  com-
               plex *z, long ldz, long *info);

PURPOSE

     cstedc computes all eigenvalues and,  optionally,  eigenvec-
     tors  of a symmetric tridiagonal matrix using the divide and
     conquer method.  The eigenvectors of a full or band  complex
     Hermitian  matrix  can  also be found if CHETRD or CHPTRD or
     CHBTRD has been used to reduce this  matrix  to  tridiagonal
     form.

     This code 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.  See SLAED3 for details.

ARGUMENTS

     COMPZ (input)
               = 'N':  Compute eigenvalues only.
               = 'I':  Compute eigenvectors of tridiagonal matrix
               also.
               = 'V':  Compute eigenvectors of original Hermitian
               matrix  also.   On  entry,  Z contains the unitary
               matrix used to reduce the original matrix to  tri-
               diagonal form.

     N (input) The dimension of the symmetric tridiagonal matrix.
               N >= 0.

     D (input/output)
               On entry, the diagonal elements of the tridiagonal
               matrix.   On exit, if INFO = 0, the eigenvalues in
               ascending order.

     E (input/output)
               On entry, the subdiagonal elements of the tridiag-
               onal matrix.  On exit, E has been destroyed.

     Z (input) On entry, if COMPZ =  'V',  then  Z  contains  the
               unitary  matrix used in the reduction to tridiago-
               nal form.  On exit, if INFO = 0, then if  COMPZ  =
               'V',  Z  contains  the orthonormal eigenvectors of
               the original Hermitian matrix, and if COMPZ = 'I',
               Z  contains  the  orthonormal  eigenvectors of the
               symmetric tridiagonal matrix.  If   COMPZ  =  'N',
               then Z is not referenced.

     LDZ (input)
               The leading dimension of the array Z.  LDZ  >=  1.
               If eigenvectors are desired, then LDZ >= max(1,N).

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

     LWORK (input)
               The dimension of the array WORK.  If COMPZ  =  'N'
               or  'I',  or N <= 1, LWORK must be at least 1.  If
               COMPZ = 'V' and N > 1, LWORK must be at least N*N.

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

     LRWORK (input)
               The dimension of the array RWORK.  If COMPZ =  'N'
               or  N <= 1, LRWORK must be at least 1.  If COMPZ =
               'V' and N > 1, LRWORK must be at least 1 +  3*N  +
               2*N*lg  N  +  3*N**2  ,  where  lg( N ) = smallest
               integer k such that 2**k >= N.  If COMPZ = 'I' and
               N > 1, LRWORK must be at least 1 + 4*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 COMPZ =  'N'
               or  N <= 1, LIWORK must be at least 1.  If COMPZ =
               'V' or N > 1,  LIWORK must be at least 6 +  6*N  +
               5*N*lg  N.   If COMPZ = 'I' or N > 1,  LIWORK must
               be at least 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:  The algorithm failed to  compute  an  eigen-
               value while working on the submatrix lying in rows
               and columns INFO/(N+1) through mod(INFO,N+1).

FURTHER DETAILS

     Based on contributions by
        Jeff Rutter, Computer  Science  Division,  University  of
     California
        at Berkeley, USA