Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dstebz (3p)

Name

dstebz - compute the eigenvalues of a symmetric tridiagonal matrix T

Synopsis

SUBROUTINE DSTEBZ(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(*)
DOUBLE PRECISION VL, VU, ABSTOL
DOUBLE PRECISION D(*), E(*), W(*), WORK(*)

SUBROUTINE DSTEBZ_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(*)
DOUBLE PRECISION VL, VU, ABSTOL
DOUBLE PRECISION 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(8) :: VL, VU, ABSTOL
REAL(8), 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(8) :: VL, VU, ABSTOL
REAL(8), DIMENSION(:) :: D, E, W, WORK




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           dstebz(3P)



NAME
       dstebz - compute the eigenvalues of a symmetric tridiagonal matrix T


SYNOPSIS
       SUBROUTINE DSTEBZ(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(*)
       DOUBLE PRECISION VL, VU, ABSTOL
       DOUBLE PRECISION D(*), E(*), W(*), WORK(*)

       SUBROUTINE DSTEBZ_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(*)
       DOUBLE PRECISION VL, VU, ABSTOL
       DOUBLE PRECISION 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(8) :: VL, VU, ABSTOL
       REAL(8), 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(8) :: VL, VU, ABSTOL
       REAL(8), DIMENSION(:) :: D, E, W, WORK




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       dstebz 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)
                 = 'A': ("All")   all eigenvalues will be found.
                 =  'V':  ("Value")  all eigenvalues in the half-open interval
                 (VL, VU] will be found.  = 'I': ("Index") the  IL-th  through
                 IU-th eigenvalues (of the entire matrix) will be found.


       ORDER (input)
                 = 'B': ("By Block") the eigenvalues will be grouped by split-
                 off block (see IBLOCK, ISPLIT) and ordered from  smallest  to
                 largest  within  the block.  = 'E': ("Entire matrix") the ei-
                 genvalues for the entire matrix will be ordered from smallest
                 to largest.


       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  small-
                 est 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*DLAMCH('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 eigenval-
                 ues.    (DSTEBZ   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.
                 (DSTEBZ 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)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  some or all of the eigenvalues failed to converge or
                 were not computed:
                 =1  or  3: Bisection failed to converge for some eigenvalues;
                 these eigenvalues are flagged by  a  negative  block  number.
                 The  effect is that the eigenvalues may not be as accurate as
                 the absolute and  relative  tolerances.   This  is  generally
                 caused  by  unexpectedly  inaccurate  arithmetic.   =2  or 3:
                 RANGE='I' only: Not all of the eigenvalues IL:IU were  found.
                 Effect: M < IU+1-IL
                 Cause:   non-monotonic arithmetic, causing the Sturm sequence
                 to be non-monotonic.  Cure:   recalculate,  using  RANGE='A',
                 and pick
                 out eigenvalues IL:IU.  = 4:    RANGE='I', and the Gershgorin
                 interval initially used was too small.  No  eigenvalues  were
                 computed.




                                  7 Nov 2015                        dstebz(3P)