Contents


NAME

     ssbevd - compute all the eigenvalues and, optionally, eigen-
     vectors of a real symmetric band matrix A

SYNOPSIS

     SUBROUTINE SSBEVD(JOBZ, UPLO, N, KD, AB, LDAB, W, Z, LDZ, WORK,
           LWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     INTEGER N, KD, LDAB, LDZ, LWORK, LIWORK, INFO
     INTEGER IWORK(*)
     REAL AB(LDAB,*), W(*), Z(LDZ,*), WORK(*)

     SUBROUTINE SSBEVD_64(JOBZ, UPLO, N, KD, AB, LDAB, W, Z, LDZ, WORK,
           LWORK, IWORK, LIWORK, INFO)

     CHARACTER * 1 JOBZ, UPLO
     INTEGER*8 N, KD, LDAB, LDZ, LWORK, LIWORK, INFO
     INTEGER*8 IWORK(*)
     REAL AB(LDAB,*), W(*), Z(LDZ,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE SBEVD(JOBZ, UPLO, [N], KD, AB, [LDAB], W, Z, [LDZ], [WORK],
            [LWORK], [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     INTEGER :: N, KD, LDAB, LDZ, LWORK, LIWORK, INFO
     INTEGER, DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: W, WORK
     REAL, DIMENSION(:,:) :: AB, Z

     SUBROUTINE SBEVD_64(JOBZ, UPLO, [N], KD, AB, [LDAB], W, Z, [LDZ],
            [WORK], [LWORK], [IWORK], [LIWORK], [INFO])

     CHARACTER(LEN=1) :: JOBZ, UPLO
     INTEGER(8) :: N, KD, LDAB, LDZ, LWORK, LIWORK, INFO
     INTEGER(8), DIMENSION(:) :: IWORK
     REAL, DIMENSION(:) :: W, WORK
     REAL, DIMENSION(:,:) :: AB, Z

  C INTERFACE
     #include <sunperf.h>

     void ssbevd(char jobz, char uplo, int n, int kd, float  *ab,
               int ldab, float *w, float *z, int ldz, int *info);
     void ssbevd_64(char jobz, char uplo, long n, long kd,  float
               *ab, long ldab, float *w, float *z, long ldz, long
               *info);

PURPOSE

     ssbevd computes all the eigenvalues and, optionally,  eigen-
     vectors  of  a real symmetric band matrix A. 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 triangle of A is stored;
               = 'L':  Lower triangle of A is stored.

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

     KD (input)
               The number of superdiagonals of the  matrix  A  if
               UPLO  = 'U', or the number of subdiagonals if UPLO
               = 'L'.  KD >= 0.

     AB (input/output)
               On entry, the upper or lower triangle of the  sym-
               metric  band  matrix  A,  stored in the first KD+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(kd+1+i-j,j) = A(i,j)  for  max(1,j-
               kd)<=i<=j;  if UPLO = 'L', AB(1+i-j,j)    = A(i,j)
               for j<=i<=min(n,j+kd).

               On exit, AB is  overwritten  by  values  generated
               during the reduction to tridiagonal form.  If UPLO
               = 'U', the first superdiagonal and the diagonal of
               the  tridiagonal  matrix T are returned in rows KD
               and KD+1 of AB, and if UPLO =  'L',  the  diagonal
               and  first  subdiagonal  of  T are returned in the
               first two rows of AB.

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

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

     Z (output)
               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  W(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  N  <=  1,
               LWORK  must be at least 1.  If JOBZ  = 'N' and N >
               2, LWORK must be at least 2*N.  If JOBZ  = 'V' and
               N  >  2, LWORK must be at least ( 1 + 5*N + 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.

     IWORK (workspace/output)
               On exit, if INFO = 0, IWORK(1) returns the optimal
               LIWORK.
     LIWORK (input)
               The dimension of the array LIWORK.  If JOBZ  = 'N'
               or  N <= 1, LIWORK must be at least 1.  If JOBZ  =
               'V' and N > 2, 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 an intermediate
               tridiagonal form did not converge to zero.