sstebz


NAME

sstebz - compute the eigenvalues of a symmetric tridiagonal matrix T


SYNOPSIS

  SUBROUTINE SSTEBZ( RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E, M, 
 *      NSPLIT, W, IBLOCK, ISPLIT, WORK, IWORK, INFO)
  CHARACTER * 1 RANGE, ORDER
  INTEGER N, IL, IU, M, NSPLIT, INFO
  INTEGER IBLOCK(*), ISPLIT(*), IWORK(*)
  REAL VL, VU, ABSTOL
  REAL D(*), E(*), W(*), WORK(*)
 
  SUBROUTINE SSTEBZ_64( RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E, 
 *      M, NSPLIT, W, IBLOCK, ISPLIT, WORK, IWORK, INFO)
  CHARACTER * 1 RANGE, ORDER
  INTEGER*8 N, IL, IU, M, NSPLIT, INFO
  INTEGER*8 IBLOCK(*), ISPLIT(*), IWORK(*)
  REAL VL, VU, ABSTOL
  REAL D(*), E(*), W(*), WORK(*)
 

F95 INTERFACE

  SUBROUTINE STEBZ( RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E, M, 
 *       NSPLIT, W, IBLOCK, ISPLIT, [WORK], [IWORK], [INFO])
  CHARACTER(LEN=1) :: RANGE, ORDER
  INTEGER :: N, IL, IU, M, NSPLIT, INFO
  INTEGER, DIMENSION(:) :: IBLOCK, ISPLIT, IWORK
  REAL :: VL, VU, ABSTOL
  REAL, DIMENSION(:) :: D, E, W, WORK
 
  SUBROUTINE STEBZ_64( RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E, 
 *       M, NSPLIT, W, IBLOCK, ISPLIT, [WORK], [IWORK], [INFO])
  CHARACTER(LEN=1) :: RANGE, ORDER
  INTEGER(8) :: N, IL, IU, M, NSPLIT, INFO
  INTEGER(8), DIMENSION(:) :: IBLOCK, ISPLIT, IWORK
  REAL :: VL, VU, ABSTOL
  REAL, DIMENSION(:) :: D, E, W, WORK
 

C INTERFACE

#include <sunperf.h>

void sstebz(char range, char order, int n, float vl, float vu, int il, int iu, float abstol, float *d, float *e, int *m, int *nsplit, float *w, int *iblock, int *isplit, int *info);

void sstebz_64(char range, char order, long n, float vl, float vu, long il, long iu, float abstol, float *d, float *e, long *m, long *nsplit, float *w, long *iblock, long *isplit, long *info);


PURPOSE

sstebz computes the eigenvalues of a symmetric tridiagonal matrix T. The user may ask for all eigenvalues, all eigenvalues in the half-open interval (VL, VU], or the IL-th through IU-th eigenvalues.

To avoid overflow, the matrix must be scaled so that its

largest element is no greater than overflow**(1/2) *

underflow**(1/4) in absolute value, and for greatest

accuracy, it should not be much smaller than that.

See W. Kahan "Accurate Eigenvalues of a Symmetric Tridiagonal Matrix", Report CS41, Computer Science Dept., Stanford

University, July 21, 1966.


ARGUMENTS

* RANGE (input)
* ORDER (input)
* N (input)
The order of the tridiagonal matrix T. N >= 0.

* VL (input)
If RANGE='V', the lower and upper bounds of the interval to be searched for eigenvalues. Eigenvalues less than or equal to VL, or greater than VU, will not be returned. 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.

* ABSTOL (input)
The absolute tolerance for the eigenvalues. An eigenvalue (or cluster) is considered to be located if it has been determined to lie in an interval whose width is ABSTOL or less. If ABSTOL is less than or equal to zero, then ULP*|T| will be used, where |T| means the 1-norm of T.

Eigenvalues will be computed most accurately when ABSTOL is set to twice the underflow threshold 2*SLAMCH('S'), not zero.

* D (input)
The n diagonal elements of the tridiagonal matrix T.

* E (input)
The (n-1) off-diagonal elements of the tridiagonal matrix T.

* M (output)
The actual number of eigenvalues found. 0 <= M <= N. (See also the description of INFO=2,3.)

* NSPLIT (output)
The number of diagonal blocks in the matrix T. 1 <= NSPLIT <= N.

* W (output)
On exit, the first M elements of W will contain the eigenvalues. (SSTEBZ may use the remaining N-M elements as workspace.)

* IBLOCK (output)
At each row/column j where E(j) is zero or small, the matrix T is considered to split into a block diagonal matrix. On exit, if INFO = 0, IBLOCK(i) specifies to which block (from 1 to the number of blocks) the eigenvalue W(i) belongs. (SSTEBZ may use the remaining N-M elements as workspace.)

* ISPLIT (output)
The splitting points, at which T breaks up into submatrices. The first submatrix consists of rows/columns 1 to ISPLIT(1), the second of rows/columns ISPLIT(1)+1 through ISPLIT(2), etc., and the NSPLIT-th consists of rows/columns ISPLIT(NSPLIT-1)+1 through ISPLIT(NSPLIT)=N. (Only the first NSPLIT elements will actually be used, but since the user cannot know a priori what value NSPLIT will have, N words must be reserved for ISPLIT.)

* WORK (workspace)
dimension(4*N)

* IWORK (workspace)
dimension(3*N)

* INFO (output)