Contents


NAME

     sstevd - compute all eigenvalues and, optionally,  eigenvec-
     tors of a real symmetric tridiagonal matrix

SYNOPSIS

     SUBROUTINE SSTEVD(JOBZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK, LIWORK,
           INFO)

     CHARACTER * 1 JOBZ
     INTEGER N, LDZ, LWORK, LIWORK, INFO
     INTEGER IWORK(*)
     REAL D(*), E(*), Z(LDZ,*), WORK(*)

     SUBROUTINE SSTEVD_64(JOBZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK,
           LIWORK, INFO)

     CHARACTER * 1 JOBZ
     INTEGER*8 N, LDZ, LWORK, LIWORK, INFO
     INTEGER*8 IWORK(*)
     REAL D(*), E(*), Z(LDZ,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE STEVD(JOBZ, N, D, E, Z, [LDZ], [WORK], [LWORK], [IWORK],
            [LIWORK], [INFO])

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

     SUBROUTINE STEVD_64(JOBZ, N, D, E, Z, [LDZ], [WORK], [LWORK], [IWORK],
            [LIWORK], [INFO])

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

  C INTERFACE
     #include <sunperf.h>

     void sstevd(char jobz, int n, float *d, float *e, float  *z,
               int ldz, int *info);
     void sstevd_64(char jobz, long n, float *d, float *e,  float
               *z, long ldz, long *info);

PURPOSE

     sstevd computes all eigenvalues and,  optionally,  eigenvec-
     tors of a real symmetric tridiagonal matrix. 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.

     N (input) The order of the matrix.  N >= 0.

     D (input/output)
               On entry, the n diagonal elements of the tridiago-
               nal  matrix  A.   On exit, if INFO = 0, the eigen-
               values in ascending order.

     E (input/output)
               On entry, the (n-1) subdiagonal  elements  of  the
               tridiagonal  matrix A, stored in elements 1 to N-1
               of E; E(N) need not be set, but  is  used  by  the
               routine.   On  exit,  the  contents  of E are des-
               troyed.

     Z (input) If JOBZ = 'V', then if INFO = 0,  Z  contains  the
               orthonormal eigenvectors of the matrix A, with the
               i-th column of Z holding the  eigenvector  associ-
               ated  with  D(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 >= max(1,N).
     WORK (workspace)
               dimension (LWORK) On exit, if INFO  =  0,  WORK(1)
               returns the optimal LWORK.

     LWORK (input)
               The dimension of the array WORK.  If JOBZ   =  'N'
               or  N <= 1 then LWORK must be at least 1.  If JOBZ
               = 'V' and N > 1 then LWORK must be at least ( 1  +
               4*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.

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

     LIWORK (input)
               The dimension of the array IWORK.  If JOBZ  =  'N'
               or N <= 1 then LIWORK must be at least 1.  If JOBZ
               = 'V' and N > 1  then  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:  if INFO = i, the algorithm  failed  to  con-
               verge;  i  off-diagonal elements of E did not con-
               verge to zero.