Contents


NAME

     sstevx  -  compute  selected  eigenvalues  and,  optionally,
     eigenvectors of a real symmetric tridiagonal matrix A

SYNOPSIS

     SUBROUTINE SSTEVX(JOBZ, RANGE, N, DIAG, OFFD, VL, VU, IL, IU, ABTOL,
           NFOUND, W, Z, LDZ, WORK, IWORK2, IFAIL, INFO)

     CHARACTER * 1 JOBZ, RANGE
     INTEGER N, IL, IU, NFOUND, LDZ, INFO
     INTEGER IWORK2(*), IFAIL(*)
     REAL VL, VU, ABTOL
     REAL DIAG(*), OFFD(*), W(*), Z(LDZ,*), WORK(*)

     SUBROUTINE SSTEVX_64(JOBZ, RANGE, N, DIAG, OFFD, VL, VU, IL, IU,
           ABTOL, NFOUND, W, Z, LDZ, WORK, IWORK2, IFAIL, INFO)

     CHARACTER * 1 JOBZ, RANGE
     INTEGER*8 N, IL, IU, NFOUND, LDZ, INFO
     INTEGER*8 IWORK2(*), IFAIL(*)
     REAL VL, VU, ABTOL
     REAL DIAG(*), OFFD(*), W(*), Z(LDZ,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE STEVX(JOBZ, RANGE, N, DIAG, OFFD, VL, VU, IL, IU, ABTOL,
            NFOUND, W, Z, [LDZ], [WORK], [IWORK2], IFAIL, [INFO])

     CHARACTER(LEN=1) :: JOBZ, RANGE
     INTEGER :: N, IL, IU, NFOUND, LDZ, INFO
     INTEGER, DIMENSION(:) :: IWORK2, IFAIL
     REAL :: VL, VU, ABTOL
     REAL, DIMENSION(:) :: DIAG, OFFD, W, WORK
     REAL, DIMENSION(:,:) :: Z

     SUBROUTINE STEVX_64(JOBZ, RANGE, N, DIAG, OFFD, VL, VU, IL, IU,
            ABTOL, NFOUND, W, Z, [LDZ], [WORK], [IWORK2], IFAIL, [INFO])

     CHARACTER(LEN=1) :: JOBZ, RANGE
     INTEGER(8) :: N, IL, IU, NFOUND, LDZ, INFO
     INTEGER(8), DIMENSION(:) :: IWORK2, IFAIL
     REAL :: VL, VU, ABTOL
     REAL, DIMENSION(:) :: DIAG, OFFD, W, WORK
     REAL, DIMENSION(:,:) :: Z

  C INTERFACE
     #include <sunperf.h>
     void sstevx(char jobz, char range, int n, float *diag, float
               *offd,  float  vl, float vu, int il, int iu, float
               abtol, int *nfound, float *w, float *z,  int  ldz,
               int *ifail, int *info);

     void sstevx_64(char jobz, char range, long n,  float  *diag,
               float *offd, float vl, float vu, long il, long iu,
               float abtol, long *nfound,  float  *w,  float  *z,
               long ldz, long *ifail, long *info);

PURPOSE

     sstevx computes selected eigenvalues and, optionally, eigen-
     vectors  of  a  real symmetric tridiagonal matrix A.  Eigen-
     values and eigenvectors can be selected by specifying either
     a  range  of  values  or  a range of indices for the desired
     eigenvalues.

ARGUMENTS

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

     RANGE (input)
               = 'A': all eigenvalues will be found.
               = 'V': all eigenvalues in the  half-open  interval
               (VL,VU]  will  be found.  = 'I': the IL-th through
               IU-th eigenvalues will be found.

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

     DIAG (input/output)
               On entry, the n diagonal elements of the tridiago-
               nal  matrix A.  On exit, DIAG may be multiplied by
               a constant factor chosen to  avoid  over/underflow
               in computing the eigenvalues.

     OFFD (input/output)
               On entry, the (n-1) subdiagonal  elements  of  the
               tridiagonal matrix A in elements 1 to N-1 of OFFD;
               OFFD(N) need not be set.  On  exit,  OFFD  may  be
               multiplied  by  a  constant factor chosen to avoid
               over/underflow in computing the eigenvalues.

     VL (input)
               If RANGE='V', the lower and upper  bounds  of  the
               interval  to be searched for eigenvalues. VL < VU.
               Not referenced if RANGE = 'A' or 'I'.

     VU (input)
               See the description of VL.

     IL (input)
               If RANGE='I', the indices (in ascending order)  of
               the   smallest   and  largest  eigenvalues  to  be
               returned.  1 <= IL <= IU <= N, if N > 0;  IL  =  1
               and  IU  =  0 if N = 0.  Not referenced if RANGE =
               'A' or 'V'.

     IU (input)
               See the description of IL.

     ABTOL (input)
               The absolute error tolerance for the  eigenvalues.
               An approximate eigenvalue is accepted as converged
               when it is determined to lie in an interval  [a,b]
               of width less than or equal to

               ABTOL + EPS *   max( |a|,|b| ) ,

               where EPS is the machine precision.  If  ABTOL  is
               less than or equal to zero, then  EPS*|T|  will be
               used in its place, where |T| is the 1-norm of  the
               tridiagonal matrix.

               Eigenvalues will be computed most accurately  when
               ABTOL  is  set  to  twice  the underflow threshold
               2*SLAMCH('S'), not zero.  If this routine  returns
               with INFO>0, indicating that some eigenvectors did
               not converge, try setting ABTOL to 2*SLAMCH('S').

               See "Computing Small Singular Values of Bidiagonal
               Matrices  with Guaranteed High Relative Accuracy,"
               by Demmel and Kahan, LAPACK Working Note #3.

     NFOUND (output)
               The total  number  of  eigenvalues  found.   0  <=
               NFOUND  <=  N.  If RANGE = 'A', NFOUND = N, and if
               RANGE = 'I', NFOUND = IU-IL+1.

     W (output)
               The first NFOUND  elements  contain  the  selected
               eigenvalues in ascending order.

     Z (input) If JOBZ = 'V', then if INFO = 0, the first  NFOUND
               columns  of Z contain the orthonormal eigenvectors
               of the matrix  A  corresponding  to  the  selected
               eigenvalues, with the i-th column of Z holding the
               eigenvector associated with W(i).  If an eigenvec-
               tor fails to converge (INFO > 0), then that column
               of Z contains  the  latest  approximation  to  the
               eigenvector,  and  the index of the eigenvector is
               returned in IFAIL.  If JOBZ = 'N', then Z  is  not
               referenced.   Note:  the  user must ensure that at
               least max(1,NFOUND) columns are  supplied  in  the
               array Z; if RANGE = 'V', the exact value of NFOUND
               is not known in advance and an upper bound must be
               used.

     LDZ (input)
               The leading dimension of the array Z.  LDZ  >=  1,
               and if JOBZ = 'V', LDZ >= max(1,N).

     WORK (workspace)
               dimension(5*N)

     IWORK2 (workspace)

     IFAIL (output)
               If JOBZ = 'V', then if INFO = 0, the first  NFOUND
               elements  of  IFAIL  are  zero.  If INFO > 0, then
               IFAIL contains the  indices  of  the  eigenvectors
               that  failed  to  converge.   If  JOBZ = 'N', then
               IFAIL is not referenced.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value
               > 0:  if INFO = i, then i eigenvectors  failed  to
               converge.   Their  indices  are  stored  in  array
               IFAIL.