SSTEGR2(3) ScaLAPACK routine of NEC Numeric Library Collection SSTEGR2(3) NAME SSTEGR2 - computes selected eigenvalues and, optionally, eigenvectors of a real symmetric tridiagonal matrix T SYNOPSIS SUBROUTINE SSTEGR2( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, M, W, Z, LDZ, NZC, ISUPPZ, WORK, LWORK, IWORK, LIWORK, DOL, DOU, ZOFFSET, INFO ) CHARACTER JOBZ, RANGE INTEGER DOL, DOU, IL, INFO, IU, LDZ, NZC, LIWORK, LWORK, M, N, ZOFFSET REAL VL, VU INTEGER ISUPPZ( * ), IWORK( * ) REAL D( * ), E( * ), W( * ), WORK( * ) REAL Z( LDZ, * ) PURPOSE SSTEGR2 computes selected eigenvalues and, optionally, eigenvectors of a real symmetric tridiagonal matrix T. It is invoked in the ScaLAPACK MRRR driver PDSYEVR and the corresponding Hermitian version either when only eigenvalues are to be computed, or when only a single processor is used (the sequential-like case). SSTEGR2 has been adapted from LAPACK's SSTEGR. Please note the follow- ing crucial changes. 1. The calling sequence has two additional INTEGER parameters, DOL and DOU, that should satisfy M>=DOU>=DOL>=1. SSTEGR2 ONLY computes the eigenpairs corresponding to eigenvalues DOL through DOU in W. (That is, instead of computing the eigenpairs 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 is M = DOU - DOL + 1. This concerns the case where only eigenvalues are computed, but on more than one processor. Thus, in this case M refers to the number of eigenvalues computed on this processor. 3. 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 the selected eigenvalues in ascending order. Note that immediately after exiting this rou- tine, only the eigenvalues from position DOL:DOU are to reli- able on this processor because the eigenvalue computation is done in parallel. Other processors will hold reliable information on other parts of the W array. This information is communicated in the ScaLA- PACK driver. Z (output) REAL array, dimension (LDZ, max(1,M) ) If JOBZ = 'V', and if INFO = 0, then the first M columns of Z contain some of 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 can be computed with a workspace query by setting NZC = -1, see below. 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. ISUPPZ (output) INTEGER ARRAY, dimension ( 2*max(1,M) ) The support of the eigenvectors in Z, i.e., the indices indi- cating the nonzero elements in Z. The i-th computed eigenvector is nonzero only in elements ISUPPZ( 2*i-1 ) through ISUPPZ( 2*i ). This is relevant in the case when the matrix is split. ISUPPZ is only set if N>2. 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 the eigenvalues W(1:M), only eigenvectors Z(:,DOL) to Z(:,DOU) are computed. If DOL > 1, then Z(:,DOL-1-ZOFFSET) is used and overwritten. If DOU < M, then Z(:,DOU+1-ZOFFSET) is used and overwritten. ZOFFSET (input) INTEGER Offset for storing the eigenpairs when Z is distributed in 1D- cyclic fashion 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 SLARRE2, if INFO = 20X, internal error in SLARRV. Here, the digit X = ABS( IINFO ) < 10, where IINFO is the nonzero error code returned by SLARRE2 or SLARRV, respectively. ScaLAPACK routine 31 October 2017 SSTEGR2(3)