Contents
     dstegr - (a) Compute T-sigma_i = L_i D_i  L_i^T,  such  that
     L_i D_i L_i^T  is a relatively robust representation
     SUBROUTINE DSTEGR(JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL, M, W,
           Z, LDZ, ISUPPZ, WORK, LWORK, IWORK, LIWORK, INFO)
     CHARACTER * 1 JOBZ, RANGE
     INTEGER N, IL, IU, M, LDZ, LWORK, LIWORK, INFO
     INTEGER ISUPPZ(*), IWORK(*)
     DOUBLE PRECISION VL, VU, ABSTOL
     DOUBLE PRECISION D(*), E(*), W(*), Z(LDZ,*), WORK(*)
     SUBROUTINE DSTEGR_64(JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL, M,
           W, Z, LDZ, ISUPPZ, WORK, LWORK, IWORK, LIWORK, INFO)
     CHARACTER * 1 JOBZ, RANGE
     INTEGER*8 N, IL, IU, M, LDZ, LWORK, LIWORK, INFO
     INTEGER*8 ISUPPZ(*), IWORK(*)
     DOUBLE PRECISION VL, VU, ABSTOL
     DOUBLE PRECISION D(*), E(*), W(*), Z(LDZ,*), WORK(*)
  F95 INTERFACE
     SUBROUTINE STEGR(JOBZ, RANGE, [N], D, E, VL, VU, IL, IU, ABSTOL, M,
            W, Z, [LDZ], ISUPPZ, [WORK], [LWORK], [IWORK], [LIWORK], [INFO])
     CHARACTER(LEN=1) :: JOBZ, RANGE
     INTEGER :: N, IL, IU, M, LDZ, LWORK, LIWORK, INFO
     INTEGER, DIMENSION(:) :: ISUPPZ, IWORK
     REAL(8) :: VL, VU, ABSTOL
     REAL(8), DIMENSION(:) :: D, E, W, WORK
     REAL(8), DIMENSION(:,:) :: Z
     SUBROUTINE STEGR_64(JOBZ, RANGE, [N], D, E, VL, VU, IL, IU, ABSTOL,
            M, W, Z, [LDZ], ISUPPZ, [WORK], [LWORK], [IWORK], [LIWORK], [INFO])
     CHARACTER(LEN=1) :: JOBZ, RANGE
     INTEGER(8) :: N, IL, IU, M, LDZ, LWORK, LIWORK, INFO
     INTEGER(8), DIMENSION(:) :: ISUPPZ, IWORK
     REAL(8) :: VL, VU, ABSTOL
     REAL(8), DIMENSION(:) :: D, E, W, WORK
     REAL(8), DIMENSION(:,:) :: Z
  C INTERFACE
     #include <sunperf.h>
     void dstegr(char jobz, char range, int n, double *d,  double
               *e,  double  vl, double vu, int il, int iu, double
               abstol, int *m, double *w, double *z, int ldz, int
               *isuppz, int *info);
     void dstegr_64(char jobz, char range,  long  n,  double  *d,
               double *e, double vl, double vu, long il, long iu,
               double abstol, long *m, double *w, double *z, long
               ldz, long *isuppz, long *info);
     dstegr b) Compute the  eigenvalues,  lambda_j,  of  L_i  D_i
     L_i^T to high
            relative accuracy by the dqds algorithm,
        (c) If there is a cluster of close eigenvalues,  "choose"
     sigma_i
            close to the cluster, and go to step (a),
        (d) Given the approximate eigenvalue lambda_j of L_i  D_i
     L_i^T,
            compute the corresponding eigenvector by forming a
            rank-revealing twisted factorization.
     The desired accuracy of the output can be specified  by  the
     input parameter ABSTOL.
     For more details, see "A new O(n^2) algorithm for  the  sym-
     metric   tridiagonal   eigenvalue/eigenvector  problem",  by
     Inderjit Dhillon, Computer Science Division Technical Report
     No. UCB/CSD-97-971, UC Berkeley, May 1997.
     Note 1 : Currently DSTEGR is only set up to find ALL  the  n
     eigenvalues and eigenvectors of T in O(n^2) time
     Note 2 : Currently the routine  DSTEIN  is  called  when  an
     appropriate  sigma_i  cannot  be  chosen  in step (c) above.
     DSTEIN invokes modified Gram-Schmidt  when  eigenvalues  are
     close.
     Note 3 : DSTEGR works only on machines which follow ieee-754
     floating-point  standard in their handling of infinities and
     NaNs.  Normal execution of DSTEGR may create NaNs and infin-
     ities  and hence may abort due to a floating point exception
     in environments which do not conform to the ieee standard.
     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.
     D (input/output)
               On entry, the n diagonal elements of the tridiago-
               nal matrix T. On exit, D is overwritten.
     E (input/output)
               On entry, the (n-1) subdiagonal  elements  of  the
               tridiagonal  matrix  T  in elements 1 to N-1 of E;
               E(N) need not be set.  On exit, E is overwritten.
     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.
     ABSTOL (input)
               The   absolute    error    tolerance    for    the
               eigenvalues/eigenvectors.   IF  JOBZ  =  'V',  the
               eigenvalues and eigenvectors output have  residual
               norms  bounded  by  ABSTOL,  and  the dot products
               between  different  eigenvectors  are  bounded  by
               ABSTOL.  If  ABSTOL  is  less than N*EPS*|T|, then
               N*EPS*|T| will be used in its place, where EPS  is
               the machine precision and |T| is the 1-norm of the
               tridiagonal matrix. The eigenvalues  are  computed
               to  an accuracy of EPS*|T| irrespective of ABSTOL.
               If high relative accuracy is important, set ABSTOL
               to  DLAMCH( 'Safe minimum' ).  See Barlow and Dem-
               mel "Computing  Accurate  Eigensystems  of  Scaled
               Diagonally Dominant Matrices", LAPACK Working Note
               #7 for a discussion of which matrices define their
               eigenvalues to high relative accuracy.
     M (output)
               The total number of eigenvalues found.  0 <= M  <=
               N.  If RANGE = 'A', M = N, and if RANGE = 'I', M =
               IU-IL+1.
     W (output)
               The first M elements contain the  selected  eigen-
               values in ascending order.
     Z (input) If JOBZ = 'V', then if  INFO  =  0,  the  first  M
               columns  of Z contain the orthonormal eigenvectors
               of the matrix  T  corresponding  to  the  selected
               eigenvalues, with the i-th column of Z holding the
               eigenvector associated with W(i).  If JOBZ =  'N',
               then  Z  is  not  referenced.  Note: the user must
               ensure that at least max(1,M) columns are supplied
               in the array Z; if RANGE = 'V', the exact value of
               M 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).
     ISUPPZ (output)
               The support of the eigenvectors in  Z,  i.e.,  the
               indices  indicating the nonzero elements in Z. The
               i-th  eigenvector  is  nonzero  only  in  elements
               ISUPPZ( 2*i-1 ) through ISUPPZ( 2*i ).
     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               (and minimal) LWORK.
     LWORK (input)
               The  dimension  of  the  array  WORK.   LWORK   >=
               max(1,18*N)
               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.   LIWORK  >=
               max(1,10*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 = 1, internal error  in  SLARRE,  if
               INFO = 2, internal error in SLARRV.
     Based on contributions by
        Inderjit Dhillon, IBM Almaden, USA
        Osni Marques, LBNL/NERSC, USA