SSTEGR2A(3)   ScaLAPACK routine of NEC Numeric Library Collection  SSTEGR2A(3)



NAME
       SSTEGR2A  -  computes  selected eigenvalues and initial representations
       needed for eigenvector computations in SSTEGR2B

SYNOPSIS
       SUBROUTINE SSTEGR2A(
                           JOBZ, RANGE, N, D, E, VL, VU, IL, IU, M, W, Z, LDZ,
                           NZC,  WORK, LWORK, IWORK, LIWORK, DOL, DOU, NEEDIL,
                           NEEDIU, INDERR, NSPLIT, PIVMIN, SCALE, WL, WU, INFO
                           )

           CHARACTER       JOBZ, RANGE

           INTEGER         DOL, DOU, IL, INDERR, INFO, IU, LDZ, LIWORK, LWORK,
                           M, N, NEEDIL, NEEDIU, NSPLIT, NZC

           REAL            PIVMIN, SCALE, VL, VU, WL, WU

           INTEGER         IWORK( * )

           REAL            D( * ), E( * ), W( * ), WORK( * )

           REAL            Z( LDZ, * )

PURPOSE
       SSTEGR2A computes  selected  eigenvalues  and  initial  representations
       needed  for  eigenvector computations in SSTEGR2B. It is invoked in the
       ScaLAPACK MRRR driver PSSYEVR and the corresponding  Hermitian  version
       when both eigenvalues and eigenvectors are computed in parallel on mul-
       tiple processors. For this case, SSTEGR2A implements the FIRST part  of
       the  MRRR  algorithm,  parallel  eigenvalue computation and finding the
       root RRR. At the end of SSTEGR2A, other processors might have a part of
       the  spectrum  that is needed to continue the computation locally. Once
       this eigenvalue information has been received  by  the  processor,  the
       computation can then proceed by calling the SECOND part of the parallel
       MRRR algorithm, SSTEGR2B.

       Please note:
       1. The calling sequence has two additional INTEGER parameters,
          (compared to LAPACK's SSTEGR), these are
          DOL and DOU and should satisfy M>=DOU>=DOL>=1.
          These parameters are only relevant for the case JOBZ = 'V'.

          Globally invoked over all processors, SSTEGR2A computes
          ALL the eigenVALUES specified by RANGE.
          RANGE= 'A': all eigenvalues will be found.
               = 'V': all eigenvalues in (VL,VU] will be found.
               = 'I': the IL-th through IU-th eigenvalues will be found.

          SSTEGR2A LOCALLY only computes the eigenvalues
          corresponding to eigenvalues DOL through DOU in W. (That is,
          instead of computing the eigenvectors belonging to W(1)
          through W(M), only the eigenvectors belonging to eigenvalues
          W(DOL) through W(DOU) are computed. In this case, only the
          eigenvalues DOL:DOU are guaranteed to be fully accurate.

       2. M is NOT the number of eigenvalues specified by RANGE, but it is
          M = DOU - DOL + 1. Instead, M refers to the  number  of  eigenvalues
       computed on
          this processor.

       3. While no eigenvectors are computed in SSTEGR2A itself (this is
          done later in SSTEGR2B), the interface
          If JOBZ = 'V' then, depending on RANGE and DOL, DOU, SSTEGR2A
          might need more workspace in Z then the original SSTEGR.
          In  particular,  the arrays W and Z might not contain all the wanted
       eigenpairs
          locally, instead this information is distributed over other
          processors.


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

       RANGE   (input) CHARACTER*1
               = '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) INTEGER
               The order of the matrix.  N >= 0.

       D       (input/output) REAL array, dimension (N)
               On entry, the N diagonal elements of the tridiagonal matrix  T.
               On exit, D is overwritten.

       E       (input/output) REAL array, dimension (N)
               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
               input, but is used internally as workspace.
               On exit, E is overwritten.

       VL      (input) REAL

       VU      (input) REAL
               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'.

       IL      (input) INTEGER

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

       M       (output) INTEGER
               Globally  summed over all processors, M equals the total number
               of eigenvalues found.  0 <= M <= N.
               If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
               The local output equals M = DOU - DOL + 1.

       W       (output) REAL array, dimension (N)
               The first M elements contain  approximations  to  the  selected
               eigenvalues  in  ascending  order.  Note that immediately after
               exiting  this  routine,  only  the  eigenvalues  from  position
               DOL:DOU  are  to  reliable on this processor because the eigen-
               value computation is done in parallel.
               The other entries outside DOL:DOU are  very  crude  preliminary
               approximations.  Other  processors hold reliable information on
               these other parts of the W array.
               This information is communicated in the ScaLAPACK driver.

       Z       (output) REAL array, dimension (LDZ, max(1,M) )
               SSTEGR2A  does  not  compute  eigenvectors,  this  is  done  in
               SSTEGR2B. The argument Z as well as all related other arguments
               only appear to keep the interface consistent and to  signal  to
               the  user  that this subroutine is meant to be used when eigen-
               vectors are computed.

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

       NZC     (input) INTEGER
               The number of eigenvectors to be held in the array Z.
               If RANGE = 'A', then NZC >= max(1,N).
               If  RANGE  =  'V',  then  NZC  >=  the number of eigenvalues in
               (VL,VU].
               If RANGE = 'I', then NZC >= IU-IL+1.
               If NZC = -1, then a workspace query  is  assumed;  the  routine
               calculates the number of columns of the array Z that are needed
               to hold the eigenvectors.
               This value is returned as the first entry of the Z  array,  and
               no error message related to NZC is issued.

       WORK    (workspace/output) REAL array, dimension (LWORK)
               On exit, if INFO = 0, WORK(1) returns the optimal (and minimal)
               LWORK.

       LWORK   (input) INTEGER
               The dimension of the array WORK. LWORK >= max(1,18*N) if JOBZ =
               'V', and LWORK >= max(1,12*N) if JOBZ = '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.

       IWORK   (workspace/output) INTEGER array, dimension (LIWORK)
               On exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.

       LIWORK  (input) INTEGER
               The dimension of the array IWORK.  LIWORK >= max(1,10*N) if the
               eigenvectors  are desired, and LIWORK >= max(1,8*N) if only the
               eigenvalues are to be computed.
               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.

       DOL     (input) INTEGER

       DOU     (input) INTEGER
               From  all  the  eigenvalues W(1:M), only eigenvalues W(DOL:DOU)
               are computed.

       NEEDIL  (output) INTEGER

       NEEDIU  (output) INTEGER
               The indices of the leftmost and rightmost eigenvalues needed to
               accurately  compute  the  relevant  part  of the representation
               tree. This information can be used to find out which processors
               have  the relevant eigenvalue information needed so that it can
               be communicated.

       INDERR  (output) INTEGER
               INDERR points to the place in the work space where  the  eigen-
               value uncertainties (errors) are stored.

       NSPLIT  (output) INTEGER
               The number of blocks T splits into. 1 <= NSPLIT <= N.

       PIVMIN  (output) REAL
               The minimum pivot in the sturm sequence for T.

       SCALE   (output) REAL
               The scaling factor for the tridiagonal T.

       WL      (output) REAL

       WU      (output) REAL
               The interval (WL, WU] contains all the wanted eigenvalues.
               It is either given by the user or computed in SLARRE2A.

       INFO    (output) INTEGER
               On exit, INFO
               = 0:  successful exit
               other:if INFO = -i, the i-th argument had an illegal value
                     if INFO = 10X, internal error in SLARRE2A,
                     Here, the digit X = ABS( IINFO ) < 10, where IINFO is
                     the nonzero error code returned by SLARRE2A.



ScaLAPACK routine               31 October 2017                    SSTEGR2A(3)