File:  [local] / rpl / lapack / lapack / zheevr_2stage.f
Revision 1.2: download - view: text, annotated - select for diffs - revision graph
Sat Jun 17 11:06:47 2017 UTC (6 years, 10 months ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_27, rpl-4_1_26, HEAD
Cohérence.

    1: *> \brief <b> ZHEEVR_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for HE matrices</b>
    2: *
    3: *  @precisions fortran z -> s d c
    4: *
    5: *  =========== DOCUMENTATION ===========
    6: *
    7: * Online html documentation available at
    8: *            http://www.netlib.org/lapack/explore-html/
    9: *
   10: *> \htmlonly
   11: *> Download ZHEEVR_2STAGE + dependencies
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zheevr_2stage.f">
   13: *> [TGZ]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zheevr_2stage.f">
   15: *> [ZIP]</a>
   16: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zheevr_2stage.f">
   17: *> [TXT]</a>
   18: *> \endhtmlonly
   19: *
   20: *  Definition:
   21: *  ===========
   22: *
   23: *       SUBROUTINE ZHEEVR_2STAGE( JOBZ, RANGE, UPLO, N, A, LDA, VL, VU,
   24: *                                 IL, IU, ABSTOL, M, W, Z, LDZ, ISUPPZ,
   25: *                                 WORK, LWORK, RWORK, LRWORK, IWORK,
   26: *                                 LIWORK, INFO )
   27: *
   28: *       IMPLICIT NONE
   29: *
   30: *       .. Scalar Arguments ..
   31: *       CHARACTER          JOBZ, RANGE, UPLO
   32: *       INTEGER            IL, INFO, IU, LDA, LDZ, LIWORK, LRWORK, LWORK,
   33: *      $                   M, N
   34: *       DOUBLE PRECISION   ABSTOL, VL, VU
   35: *       ..
   36: *       .. Array Arguments ..
   37: *       INTEGER            ISUPPZ( * ), IWORK( * )
   38: *       DOUBLE PRECISION   RWORK( * ), W( * )
   39: *       COMPLEX*16         A( LDA, * ), WORK( * ), Z( LDZ, * )
   40: *       ..
   41: *
   42: *
   43: *> \par Purpose:
   44: *  =============
   45: *>
   46: *> \verbatim
   47: *>
   48: *> ZHEEVR_2STAGE computes selected eigenvalues and, optionally, eigenvectors
   49: *> of a complex Hermitian matrix A using the 2stage technique for
   50: *> the reduction to tridiagonal.  Eigenvalues and eigenvectors can
   51: *> be selected by specifying either a range of values or a range of
   52: *> indices for the desired eigenvalues.
   53: *>
   54: *> ZHEEVR_2STAGE first reduces the matrix A to tridiagonal form T with a call
   55: *> to ZHETRD.  Then, whenever possible, ZHEEVR_2STAGE calls ZSTEMR to compute
   56: *> eigenspectrum using Relatively Robust Representations.  ZSTEMR
   57: *> computes eigenvalues by the dqds algorithm, while orthogonal
   58: *> eigenvectors are computed from various "good" L D L^T representations
   59: *> (also known as Relatively Robust Representations). Gram-Schmidt
   60: *> orthogonalization is avoided as far as possible. More specifically,
   61: *> the various steps of the algorithm are as follows.
   62: *>
   63: *> For each unreduced block (submatrix) of T,
   64: *>    (a) Compute T - sigma I  = L D L^T, so that L and D
   65: *>        define all the wanted eigenvalues to high relative accuracy.
   66: *>        This means that small relative changes in the entries of D and L
   67: *>        cause only small relative changes in the eigenvalues and
   68: *>        eigenvectors. The standard (unfactored) representation of the
   69: *>        tridiagonal matrix T does not have this property in general.
   70: *>    (b) Compute the eigenvalues to suitable accuracy.
   71: *>        If the eigenvectors are desired, the algorithm attains full
   72: *>        accuracy of the computed eigenvalues only right before
   73: *>        the corresponding vectors have to be computed, see steps c) and d).
   74: *>    (c) For each cluster of close eigenvalues, select a new
   75: *>        shift close to the cluster, find a new factorization, and refine
   76: *>        the shifted eigenvalues to suitable accuracy.
   77: *>    (d) For each eigenvalue with a large enough relative separation compute
   78: *>        the corresponding eigenvector by forming a rank revealing twisted
   79: *>        factorization. Go back to (c) for any clusters that remain.
   80: *>
   81: *> The desired accuracy of the output can be specified by the input
   82: *> parameter ABSTOL.
   83: *>
   84: *> For more details, see DSTEMR's documentation and:
   85: *> - Inderjit S. Dhillon and Beresford N. Parlett: "Multiple representations
   86: *>   to compute orthogonal eigenvectors of symmetric tridiagonal matrices,"
   87: *>   Linear Algebra and its Applications, 387(1), pp. 1-28, August 2004.
   88: *> - Inderjit Dhillon and Beresford Parlett: "Orthogonal Eigenvectors and
   89: *>   Relative Gaps," SIAM Journal on Matrix Analysis and Applications, Vol. 25,
   90: *>   2004.  Also LAPACK Working Note 154.
   91: *> - Inderjit Dhillon: "A new O(n^2) algorithm for the symmetric
   92: *>   tridiagonal eigenvalue/eigenvector problem",
   93: *>   Computer Science Division Technical Report No. UCB/CSD-97-971,
   94: *>   UC Berkeley, May 1997.
   95: *>
   96: *>
   97: *> Note 1 : ZHEEVR_2STAGE calls ZSTEMR when the full spectrum is requested
   98: *> on machines which conform to the ieee-754 floating point standard.
   99: *> ZHEEVR_2STAGE calls DSTEBZ and ZSTEIN on non-ieee machines and
  100: *> when partial spectrum requests are made.
  101: *>
  102: *> Normal execution of ZSTEMR may create NaNs and infinities and
  103: *> hence may abort due to a floating point exception in environments
  104: *> which do not handle NaNs and infinities in the ieee standard default
  105: *> manner.
  106: *> \endverbatim
  107: *
  108: *  Arguments:
  109: *  ==========
  110: *
  111: *> \param[in] JOBZ
  112: *> \verbatim
  113: *>          JOBZ is CHARACTER*1
  114: *>          = 'N':  Compute eigenvalues only;
  115: *>          = 'V':  Compute eigenvalues and eigenvectors.
  116: *>                  Not available in this release.
  117: *> \endverbatim
  118: *>
  119: *> \param[in] RANGE
  120: *> \verbatim
  121: *>          RANGE is CHARACTER*1
  122: *>          = 'A': all eigenvalues will be found.
  123: *>          = 'V': all eigenvalues in the half-open interval (VL,VU]
  124: *>                 will be found.
  125: *>          = 'I': the IL-th through IU-th eigenvalues will be found.
  126: *>          For RANGE = 'V' or 'I' and IU - IL < N - 1, DSTEBZ and
  127: *>          ZSTEIN are called
  128: *> \endverbatim
  129: *>
  130: *> \param[in] UPLO
  131: *> \verbatim
  132: *>          UPLO is CHARACTER*1
  133: *>          = 'U':  Upper triangle of A is stored;
  134: *>          = 'L':  Lower triangle of A is stored.
  135: *> \endverbatim
  136: *>
  137: *> \param[in] N
  138: *> \verbatim
  139: *>          N is INTEGER
  140: *>          The order of the matrix A.  N >= 0.
  141: *> \endverbatim
  142: *>
  143: *> \param[in,out] A
  144: *> \verbatim
  145: *>          A is COMPLEX*16 array, dimension (LDA, N)
  146: *>          On entry, the Hermitian matrix A.  If UPLO = 'U', the
  147: *>          leading N-by-N upper triangular part of A contains the
  148: *>          upper triangular part of the matrix A.  If UPLO = 'L',
  149: *>          the leading N-by-N lower triangular part of A contains
  150: *>          the lower triangular part of the matrix A.
  151: *>          On exit, the lower triangle (if UPLO='L') or the upper
  152: *>          triangle (if UPLO='U') of A, including the diagonal, is
  153: *>          destroyed.
  154: *> \endverbatim
  155: *>
  156: *> \param[in] LDA
  157: *> \verbatim
  158: *>          LDA is INTEGER
  159: *>          The leading dimension of the array A.  LDA >= max(1,N).
  160: *> \endverbatim
  161: *>
  162: *> \param[in] VL
  163: *> \verbatim
  164: *>          VL is DOUBLE PRECISION
  165: *>          If RANGE='V', the lower bound of the interval to
  166: *>          be searched for eigenvalues. VL < VU.
  167: *>          Not referenced if RANGE = 'A' or 'I'.
  168: *> \endverbatim
  169: *>
  170: *> \param[in] VU
  171: *> \verbatim
  172: *>          VU is DOUBLE PRECISION
  173: *>          If RANGE='V', the upper bound of the interval to
  174: *>          be searched for eigenvalues. VL < VU.
  175: *>          Not referenced if RANGE = 'A' or 'I'.
  176: *> \endverbatim
  177: *>
  178: *> \param[in] IL
  179: *> \verbatim
  180: *>          IL is INTEGER
  181: *>          If RANGE='I', the index of the
  182: *>          smallest eigenvalue to be returned.
  183: *>          1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
  184: *>          Not referenced if RANGE = 'A' or 'V'.
  185: *> \endverbatim
  186: *>
  187: *> \param[in] IU
  188: *> \verbatim
  189: *>          IU is INTEGER
  190: *>          If RANGE='I', the index of the
  191: *>          largest eigenvalue to be returned.
  192: *>          1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
  193: *>          Not referenced if RANGE = 'A' or 'V'.
  194: *> \endverbatim
  195: *>
  196: *> \param[in] ABSTOL
  197: *> \verbatim
  198: *>          ABSTOL is DOUBLE PRECISION
  199: *>          The absolute error tolerance for the eigenvalues.
  200: *>          An approximate eigenvalue is accepted as converged
  201: *>          when it is determined to lie in an interval [a,b]
  202: *>          of width less than or equal to
  203: *>
  204: *>                  ABSTOL + EPS *   max( |a|,|b| ) ,
  205: *>
  206: *>          where EPS is the machine precision.  If ABSTOL is less than
  207: *>          or equal to zero, then  EPS*|T|  will be used in its place,
  208: *>          where |T| is the 1-norm of the tridiagonal matrix obtained
  209: *>          by reducing A to tridiagonal form.
  210: *>
  211: *>          See "Computing Small Singular Values of Bidiagonal Matrices
  212: *>          with Guaranteed High Relative Accuracy," by Demmel and
  213: *>          Kahan, LAPACK Working Note #3.
  214: *>
  215: *>          If high relative accuracy is important, set ABSTOL to
  216: *>          DLAMCH( 'Safe minimum' ).  Doing so will guarantee that
  217: *>          eigenvalues are computed to high relative accuracy when
  218: *>          possible in future releases.  The current code does not
  219: *>          make any guarantees about high relative accuracy, but
  220: *>          furutre releases will. See J. Barlow and J. Demmel,
  221: *>          "Computing Accurate Eigensystems of Scaled Diagonally
  222: *>          Dominant Matrices", LAPACK Working Note #7, for a discussion
  223: *>          of which matrices define their eigenvalues to high relative
  224: *>          accuracy.
  225: *> \endverbatim
  226: *>
  227: *> \param[out] M
  228: *> \verbatim
  229: *>          M is INTEGER
  230: *>          The total number of eigenvalues found.  0 <= M <= N.
  231: *>          If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
  232: *> \endverbatim
  233: *>
  234: *> \param[out] W
  235: *> \verbatim
  236: *>          W is DOUBLE PRECISION array, dimension (N)
  237: *>          The first M elements contain the selected eigenvalues in
  238: *>          ascending order.
  239: *> \endverbatim
  240: *>
  241: *> \param[out] Z
  242: *> \verbatim
  243: *>          Z is COMPLEX*16 array, dimension (LDZ, max(1,M))
  244: *>          If JOBZ = 'V', then if INFO = 0, the first M columns of Z
  245: *>          contain the orthonormal eigenvectors of the matrix A
  246: *>          corresponding to the selected eigenvalues, with the i-th
  247: *>          column of Z holding the eigenvector associated with W(i).
  248: *>          If JOBZ = 'N', then Z is not referenced.
  249: *>          Note: the user must ensure that at least max(1,M) columns are
  250: *>          supplied in the array Z; if RANGE = 'V', the exact value of M
  251: *>          is not known in advance and an upper bound must be used.
  252: *> \endverbatim
  253: *>
  254: *> \param[in] LDZ
  255: *> \verbatim
  256: *>          LDZ is INTEGER
  257: *>          The leading dimension of the array Z.  LDZ >= 1, and if
  258: *>          JOBZ = 'V', LDZ >= max(1,N).
  259: *> \endverbatim
  260: *>
  261: *> \param[out] ISUPPZ
  262: *> \verbatim
  263: *>          ISUPPZ is INTEGER array, dimension ( 2*max(1,M) )
  264: *>          The support of the eigenvectors in Z, i.e., the indices
  265: *>          indicating the nonzero elements in Z. The i-th eigenvector
  266: *>          is nonzero only in elements ISUPPZ( 2*i-1 ) through
  267: *>          ISUPPZ( 2*i ). This is an output of ZSTEMR (tridiagonal
  268: *>          matrix). The support of the eigenvectors of A is typically 
  269: *>          1:N because of the unitary transformations applied by ZUNMTR.
  270: *>          Implemented only for RANGE = 'A' or 'I' and IU - IL = N - 1
  271: *> \endverbatim
  272: *>
  273: *> \param[out] WORK
  274: *> \verbatim
  275: *>          WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
  276: *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
  277: *> \endverbatim
  278: *>
  279: *> \param[in] LWORK
  280: *> \verbatim
  281: *>          LWORK is INTEGER
  282: *>          The dimension of the array WORK.  
  283: *>          If JOBZ = 'N' and N > 1, LWORK must be queried.
  284: *>                                   LWORK = MAX(1, 26*N, dimension) where
  285: *>                                   dimension = max(stage1,stage2) + (KD+1)*N + N
  286: *>                                             = N*KD + N*max(KD+1,FACTOPTNB) 
  287: *>                                               + max(2*KD*KD, KD*NTHREADS) 
  288: *>                                               + (KD+1)*N + N
  289: *>                                   where KD is the blocking size of the reduction,
  290: *>                                   FACTOPTNB is the blocking used by the QR or LQ
  291: *>                                   algorithm, usually FACTOPTNB=128 is a good choice
  292: *>                                   NTHREADS is the number of threads used when
  293: *>                                   openMP compilation is enabled, otherwise =1.
  294: *>          If JOBZ = 'V' and N > 1, LWORK must be queried. Not yet available
  295: *>
  296: *>          If LWORK = -1, then a workspace query is assumed; the routine
  297: *>          only calculates the optimal sizes of the WORK, RWORK and
  298: *>          IWORK arrays, returns these values as the first entries of
  299: *>          the WORK, RWORK and IWORK arrays, and no error message
  300: *>          related to LWORK or LRWORK or LIWORK is issued by XERBLA.
  301: *> \endverbatim
  302: *>
  303: *> \param[out] RWORK
  304: *> \verbatim
  305: *>          RWORK is DOUBLE PRECISION array, dimension (MAX(1,LRWORK))
  306: *>          On exit, if INFO = 0, RWORK(1) returns the optimal
  307: *>          (and minimal) LRWORK.
  308: *> \endverbatim
  309: *>
  310: *> \param[in] LRWORK
  311: *> \verbatim
  312: *>          LRWORK is INTEGER
  313: *>          The length of the array RWORK.  LRWORK >= max(1,24*N).
  314: *>
  315: *>          If LRWORK = -1, then a workspace query is assumed; the
  316: *>          routine only calculates the optimal sizes of the WORK, RWORK
  317: *>          and IWORK arrays, returns these values as the first entries
  318: *>          of the WORK, RWORK and IWORK arrays, and no error message
  319: *>          related to LWORK or LRWORK or LIWORK is issued by XERBLA.
  320: *> \endverbatim
  321: *>
  322: *> \param[out] IWORK
  323: *> \verbatim
  324: *>          IWORK is INTEGER array, dimension (MAX(1,LIWORK))
  325: *>          On exit, if INFO = 0, IWORK(1) returns the optimal
  326: *>          (and minimal) LIWORK.
  327: *> \endverbatim
  328: *>
  329: *> \param[in] LIWORK
  330: *> \verbatim
  331: *>          LIWORK is INTEGER
  332: *>          The dimension of the array IWORK.  LIWORK >= max(1,10*N).
  333: *>
  334: *>          If LIWORK = -1, then a workspace query is assumed; the
  335: *>          routine only calculates the optimal sizes of the WORK, RWORK
  336: *>          and IWORK arrays, returns these values as the first entries
  337: *>          of the WORK, RWORK and IWORK arrays, and no error message
  338: *>          related to LWORK or LRWORK or LIWORK is issued by XERBLA.
  339: *> \endverbatim
  340: *>
  341: *> \param[out] INFO
  342: *> \verbatim
  343: *>          INFO is INTEGER
  344: *>          = 0:  successful exit
  345: *>          < 0:  if INFO = -i, the i-th argument had an illegal value
  346: *>          > 0:  Internal error
  347: *> \endverbatim
  348: *
  349: *  Authors:
  350: *  ========
  351: *
  352: *> \author Univ. of Tennessee
  353: *> \author Univ. of California Berkeley
  354: *> \author Univ. of Colorado Denver
  355: *> \author NAG Ltd.
  356: *
  357: *> \date June 2016
  358: *
  359: *> \ingroup complex16HEeigen
  360: *
  361: *> \par Contributors:
  362: *  ==================
  363: *>
  364: *>     Inderjit Dhillon, IBM Almaden, USA \n
  365: *>     Osni Marques, LBNL/NERSC, USA \n
  366: *>     Ken Stanley, Computer Science Division, University of
  367: *>       California at Berkeley, USA \n
  368: *>     Jason Riedy, Computer Science Division, University of
  369: *>       California at Berkeley, USA \n
  370: *>
  371: *> \par Further Details:
  372: *  =====================
  373: *>
  374: *> \verbatim
  375: *>
  376: *>  All details about the 2stage techniques are available in:
  377: *>
  378: *>  Azzam Haidar, Hatem Ltaief, and Jack Dongarra.
  379: *>  Parallel reduction to condensed forms for symmetric eigenvalue problems
  380: *>  using aggregated fine-grained and memory-aware kernels. In Proceedings
  381: *>  of 2011 International Conference for High Performance Computing,
  382: *>  Networking, Storage and Analysis (SC '11), New York, NY, USA,
  383: *>  Article 8 , 11 pages.
  384: *>  http://doi.acm.org/10.1145/2063384.2063394
  385: *>
  386: *>  A. Haidar, J. Kurzak, P. Luszczek, 2013.
  387: *>  An improved parallel singular value algorithm and its implementation 
  388: *>  for multicore hardware, In Proceedings of 2013 International Conference
  389: *>  for High Performance Computing, Networking, Storage and Analysis (SC '13).
  390: *>  Denver, Colorado, USA, 2013.
  391: *>  Article 90, 12 pages.
  392: *>  http://doi.acm.org/10.1145/2503210.2503292
  393: *>
  394: *>  A. Haidar, R. Solca, S. Tomov, T. Schulthess and J. Dongarra.
  395: *>  A novel hybrid CPU-GPU generalized eigensolver for electronic structure 
  396: *>  calculations based on fine-grained memory aware tasks.
  397: *>  International Journal of High Performance Computing Applications.
  398: *>  Volume 28 Issue 2, Pages 196-209, May 2014.
  399: *>  http://hpc.sagepub.com/content/28/2/196 
  400: *>
  401: *> \endverbatim
  402: *
  403: *  =====================================================================
  404:       SUBROUTINE ZHEEVR_2STAGE( JOBZ, RANGE, UPLO, N, A, LDA, VL, VU,
  405:      $                          IL, IU, ABSTOL, M, W, Z, LDZ, ISUPPZ,
  406:      $                          WORK, LWORK, RWORK, LRWORK, IWORK,
  407:      $                          LIWORK, INFO )
  408: *
  409:       IMPLICIT NONE
  410: *
  411: *  -- LAPACK driver routine (version 3.7.0) --
  412: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  413: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  414: *     June 2016
  415: *
  416: *     .. Scalar Arguments ..
  417:       CHARACTER          JOBZ, RANGE, UPLO
  418:       INTEGER            IL, INFO, IU, LDA, LDZ, LIWORK, LRWORK, LWORK,
  419:      $                   M, N
  420:       DOUBLE PRECISION   ABSTOL, VL, VU
  421: *     ..
  422: *     .. Array Arguments ..
  423:       INTEGER            ISUPPZ( * ), IWORK( * )
  424:       DOUBLE PRECISION   RWORK( * ), W( * )
  425:       COMPLEX*16         A( LDA, * ), WORK( * ), Z( LDZ, * )
  426: *     ..
  427: *
  428: *  =====================================================================
  429: *
  430: *     .. Parameters ..
  431:       DOUBLE PRECISION   ZERO, ONE, TWO
  432:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0 )
  433: *     ..
  434: *     .. Local Scalars ..
  435:       LOGICAL            ALLEIG, INDEIG, LOWER, LQUERY, TEST, VALEIG,
  436:      $                   WANTZ, TRYRAC
  437:       CHARACTER          ORDER
  438:       INTEGER            I, IEEEOK, IINFO, IMAX, INDIBL, INDIFL, INDISP,
  439:      $                   INDIWO, INDRD, INDRDD, INDRE, INDREE, INDRWK,
  440:      $                   INDTAU, INDWK, INDWKN, ISCALE, ITMP1, J, JJ,
  441:      $                   LIWMIN, LLWORK, LLRWORK, LLWRKN, LRWMIN,
  442:      $                   LWMIN, NSPLIT, LHTRD, LWTRD, KD, IB, INDHOUS
  443:       DOUBLE PRECISION   ABSTLL, ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN,
  444:      $                   SIGMA, SMLNUM, TMP1, VLL, VUU
  445: *     ..
  446: *     .. External Functions ..
  447:       LOGICAL            LSAME
  448:       INTEGER            ILAENV
  449:       DOUBLE PRECISION   DLAMCH, ZLANSY
  450:       EXTERNAL           LSAME, ILAENV, DLAMCH, ZLANSY
  451: *     ..
  452: *     .. External Subroutines ..
  453:       EXTERNAL           DCOPY, DSCAL, DSTEBZ, DSTERF, XERBLA, ZDSCAL,
  454:      $                   ZHETRD_2STAGE, ZSTEMR, ZSTEIN, ZSWAP, ZUNMTR
  455: *     ..
  456: *     .. Intrinsic Functions ..
  457:       INTRINSIC          DBLE, MAX, MIN, SQRT
  458: *     ..
  459: *     .. Executable Statements ..
  460: *
  461: *     Test the input parameters.
  462: *
  463:       IEEEOK = ILAENV( 10, 'ZHEEVR', 'N', 1, 2, 3, 4 )
  464: *
  465:       LOWER = LSAME( UPLO, 'L' )
  466:       WANTZ = LSAME( JOBZ, 'V' )
  467:       ALLEIG = LSAME( RANGE, 'A' )
  468:       VALEIG = LSAME( RANGE, 'V' )
  469:       INDEIG = LSAME( RANGE, 'I' )
  470: *
  471:       LQUERY = ( ( LWORK.EQ.-1 ) .OR. ( LRWORK.EQ.-1 ) .OR.
  472:      $         ( LIWORK.EQ.-1 ) )
  473: *
  474:       KD     = ILAENV( 17, 'DSYTRD_2STAGE', JOBZ, N, -1, -1, -1 )
  475:       IB     = ILAENV( 18, 'DSYTRD_2STAGE', JOBZ, N, KD, -1, -1 )
  476:       LHTRD  = ILAENV( 19, 'DSYTRD_2STAGE', JOBZ, N, KD, IB, -1 )
  477:       LWTRD  = ILAENV( 20, 'DSYTRD_2STAGE', JOBZ, N, KD, IB, -1 )
  478:       LWMIN  = N + LHTRD + LWTRD
  479:       LRWMIN = MAX( 1, 24*N )
  480:       LIWMIN = MAX( 1, 10*N )
  481: *
  482:       INFO = 0
  483:       IF( .NOT.( LSAME( JOBZ, 'N' ) ) ) THEN
  484:          INFO = -1
  485:       ELSE IF( .NOT.( ALLEIG .OR. VALEIG .OR. INDEIG ) ) THEN
  486:          INFO = -2
  487:       ELSE IF( .NOT.( LOWER .OR. LSAME( UPLO, 'U' ) ) ) THEN
  488:          INFO = -3
  489:       ELSE IF( N.LT.0 ) THEN
  490:          INFO = -4
  491:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  492:          INFO = -6
  493:       ELSE
  494:          IF( VALEIG ) THEN
  495:             IF( N.GT.0 .AND. VU.LE.VL )
  496:      $         INFO = -8
  497:          ELSE IF( INDEIG ) THEN
  498:             IF( IL.LT.1 .OR. IL.GT.MAX( 1, N ) ) THEN
  499:                INFO = -9
  500:             ELSE IF( IU.LT.MIN( N, IL ) .OR. IU.GT.N ) THEN
  501:                INFO = -10
  502:             END IF
  503:          END IF
  504:       END IF
  505:       IF( INFO.EQ.0 ) THEN
  506:          IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN
  507:             INFO = -15
  508:          END IF
  509:       END IF
  510: *
  511:       IF( INFO.EQ.0 ) THEN
  512:          WORK( 1 )  = LWMIN
  513:          RWORK( 1 ) = LRWMIN
  514:          IWORK( 1 ) = LIWMIN
  515: *
  516:          IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
  517:             INFO = -18
  518:          ELSE IF( LRWORK.LT.LRWMIN .AND. .NOT.LQUERY ) THEN
  519:             INFO = -20
  520:          ELSE IF( LIWORK.LT.LIWMIN .AND. .NOT.LQUERY ) THEN
  521:             INFO = -22
  522:          END IF
  523:       END IF
  524: *
  525:       IF( INFO.NE.0 ) THEN
  526:          CALL XERBLA( 'ZHEEVR_2STAGE', -INFO )
  527:          RETURN
  528:       ELSE IF( LQUERY ) THEN
  529:          RETURN
  530:       END IF
  531: *
  532: *     Quick return if possible
  533: *
  534:       M = 0
  535:       IF( N.EQ.0 ) THEN
  536:          WORK( 1 ) = 1
  537:          RETURN
  538:       END IF
  539: *
  540:       IF( N.EQ.1 ) THEN
  541:          WORK( 1 ) = 2
  542:          IF( ALLEIG .OR. INDEIG ) THEN
  543:             M = 1
  544:             W( 1 ) = DBLE( A( 1, 1 ) )
  545:          ELSE
  546:             IF( VL.LT.DBLE( A( 1, 1 ) ) .AND. VU.GE.DBLE( A( 1, 1 ) ) )
  547:      $           THEN
  548:                M = 1
  549:                W( 1 ) = DBLE( A( 1, 1 ) )
  550:             END IF
  551:          END IF
  552:          IF( WANTZ ) THEN
  553:             Z( 1, 1 ) = ONE
  554:             ISUPPZ( 1 ) = 1
  555:             ISUPPZ( 2 ) = 1
  556:          END IF
  557:          RETURN
  558:       END IF
  559: *
  560: *     Get machine constants.
  561: *
  562:       SAFMIN = DLAMCH( 'Safe minimum' )
  563:       EPS    = DLAMCH( 'Precision' )
  564:       SMLNUM = SAFMIN / EPS
  565:       BIGNUM = ONE / SMLNUM
  566:       RMIN   = SQRT( SMLNUM )
  567:       RMAX   = MIN( SQRT( BIGNUM ), ONE / SQRT( SQRT( SAFMIN ) ) )
  568: *
  569: *     Scale matrix to allowable range, if necessary.
  570: *
  571:       ISCALE = 0
  572:       ABSTLL = ABSTOL
  573:       IF (VALEIG) THEN
  574:          VLL = VL
  575:          VUU = VU
  576:       END IF
  577:       ANRM = ZLANSY( 'M', UPLO, N, A, LDA, RWORK )
  578:       IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN
  579:          ISCALE = 1
  580:          SIGMA = RMIN / ANRM
  581:       ELSE IF( ANRM.GT.RMAX ) THEN
  582:          ISCALE = 1
  583:          SIGMA = RMAX / ANRM
  584:       END IF
  585:       IF( ISCALE.EQ.1 ) THEN
  586:          IF( LOWER ) THEN
  587:             DO 10 J = 1, N
  588:                CALL ZDSCAL( N-J+1, SIGMA, A( J, J ), 1 )
  589:    10       CONTINUE
  590:          ELSE
  591:             DO 20 J = 1, N
  592:                CALL ZDSCAL( J, SIGMA, A( 1, J ), 1 )
  593:    20       CONTINUE
  594:          END IF
  595:          IF( ABSTOL.GT.0 )
  596:      $      ABSTLL = ABSTOL*SIGMA
  597:          IF( VALEIG ) THEN
  598:             VLL = VL*SIGMA
  599:             VUU = VU*SIGMA
  600:          END IF
  601:       END IF
  602: 
  603: *     Initialize indices into workspaces.  Note: The IWORK indices are
  604: *     used only if DSTERF or ZSTEMR fail.
  605: 
  606: *     WORK(INDTAU:INDTAU+N-1) stores the complex scalar factors of the
  607: *     elementary reflectors used in ZHETRD.
  608:       INDTAU = 1
  609: *     INDWK is the starting offset of the remaining complex workspace,
  610: *     and LLWORK is the remaining complex workspace size.
  611:       INDHOUS = INDTAU + N
  612:       INDWK   = INDHOUS + LHTRD
  613:       LLWORK  = LWORK - INDWK + 1
  614: 
  615: *     RWORK(INDRD:INDRD+N-1) stores the real tridiagonal's diagonal
  616: *     entries.
  617:       INDRD = 1
  618: *     RWORK(INDRE:INDRE+N-1) stores the off-diagonal entries of the
  619: *     tridiagonal matrix from ZHETRD.
  620:       INDRE = INDRD + N
  621: *     RWORK(INDRDD:INDRDD+N-1) is a copy of the diagonal entries over
  622: *     -written by ZSTEMR (the DSTERF path copies the diagonal to W).
  623:       INDRDD = INDRE + N
  624: *     RWORK(INDREE:INDREE+N-1) is a copy of the off-diagonal entries over
  625: *     -written while computing the eigenvalues in DSTERF and ZSTEMR.
  626:       INDREE = INDRDD + N
  627: *     INDRWK is the starting offset of the left-over real workspace, and
  628: *     LLRWORK is the remaining workspace size.
  629:       INDRWK = INDREE + N
  630:       LLRWORK = LRWORK - INDRWK + 1
  631: 
  632: *     IWORK(INDIBL:INDIBL+M-1) corresponds to IBLOCK in DSTEBZ and
  633: *     stores the block indices of each of the M<=N eigenvalues.
  634:       INDIBL = 1
  635: *     IWORK(INDISP:INDISP+NSPLIT-1) corresponds to ISPLIT in DSTEBZ and
  636: *     stores the starting and finishing indices of each block.
  637:       INDISP = INDIBL + N
  638: *     IWORK(INDIFL:INDIFL+N-1) stores the indices of eigenvectors
  639: *     that corresponding to eigenvectors that fail to converge in
  640: *     ZSTEIN.  This information is discarded; if any fail, the driver
  641: *     returns INFO > 0.
  642:       INDIFL = INDISP + N
  643: *     INDIWO is the offset of the remaining integer workspace.
  644:       INDIWO = INDIFL + N
  645: 
  646: *
  647: *     Call ZHETRD_2STAGE to reduce Hermitian matrix to tridiagonal form.
  648: *
  649:       CALL ZHETRD_2STAGE( JOBZ, UPLO, N, A, LDA, RWORK( INDRD ), 
  650:      $                    RWORK( INDRE ), WORK( INDTAU ),
  651:      $                    WORK( INDHOUS ), LHTRD, 
  652:      $                    WORK( INDWK ), LLWORK, IINFO )
  653: *
  654: *     If all eigenvalues are desired
  655: *     then call DSTERF or ZSTEMR and ZUNMTR.
  656: *
  657:       TEST = .FALSE.
  658:       IF( INDEIG ) THEN
  659:          IF( IL.EQ.1 .AND. IU.EQ.N ) THEN
  660:             TEST = .TRUE.
  661:          END IF
  662:       END IF
  663:       IF( ( ALLEIG.OR.TEST ) .AND. ( IEEEOK.EQ.1 ) ) THEN
  664:          IF( .NOT.WANTZ ) THEN
  665:             CALL DCOPY( N, RWORK( INDRD ), 1, W, 1 )
  666:             CALL DCOPY( N-1, RWORK( INDRE ), 1, RWORK( INDREE ), 1 )
  667:             CALL DSTERF( N, W, RWORK( INDREE ), INFO )
  668:          ELSE
  669:             CALL DCOPY( N-1, RWORK( INDRE ), 1, RWORK( INDREE ), 1 )
  670:             CALL DCOPY( N, RWORK( INDRD ), 1, RWORK( INDRDD ), 1 )
  671: *
  672:             IF (ABSTOL .LE. TWO*N*EPS) THEN
  673:                TRYRAC = .TRUE.
  674:             ELSE
  675:                TRYRAC = .FALSE.
  676:             END IF
  677:             CALL ZSTEMR( JOBZ, 'A', N, RWORK( INDRDD ),
  678:      $                   RWORK( INDREE ), VL, VU, IL, IU, M, W,
  679:      $                   Z, LDZ, N, ISUPPZ, TRYRAC,
  680:      $                   RWORK( INDRWK ), LLRWORK,
  681:      $                   IWORK, LIWORK, INFO )
  682: *
  683: *           Apply unitary matrix used in reduction to tridiagonal
  684: *           form to eigenvectors returned by ZSTEMR.
  685: *
  686:             IF( WANTZ .AND. INFO.EQ.0 ) THEN
  687:                INDWKN = INDWK
  688:                LLWRKN = LWORK - INDWKN + 1
  689:                CALL ZUNMTR( 'L', UPLO, 'N', N, M, A, LDA,
  690:      $                      WORK( INDTAU ), Z, LDZ, WORK( INDWKN ),
  691:      $                      LLWRKN, IINFO )
  692:             END IF
  693:          END IF
  694: *
  695: *
  696:          IF( INFO.EQ.0 ) THEN
  697:             M = N
  698:             GO TO 30
  699:          END IF
  700:          INFO = 0
  701:       END IF
  702: *
  703: *     Otherwise, call DSTEBZ and, if eigenvectors are desired, ZSTEIN.
  704: *     Also call DSTEBZ and ZSTEIN if ZSTEMR fails.
  705: *
  706:       IF( WANTZ ) THEN
  707:          ORDER = 'B'
  708:       ELSE
  709:          ORDER = 'E'
  710:       END IF
  711: 
  712:       CALL DSTEBZ( RANGE, ORDER, N, VLL, VUU, IL, IU, ABSTLL,
  713:      $             RWORK( INDRD ), RWORK( INDRE ), M, NSPLIT, W,
  714:      $             IWORK( INDIBL ), IWORK( INDISP ), RWORK( INDRWK ),
  715:      $             IWORK( INDIWO ), INFO )
  716: *
  717:       IF( WANTZ ) THEN
  718:          CALL ZSTEIN( N, RWORK( INDRD ), RWORK( INDRE ), M, W,
  719:      $                IWORK( INDIBL ), IWORK( INDISP ), Z, LDZ,
  720:      $                RWORK( INDRWK ), IWORK( INDIWO ), IWORK( INDIFL ),
  721:      $                INFO )
  722: *
  723: *        Apply unitary matrix used in reduction to tridiagonal
  724: *        form to eigenvectors returned by ZSTEIN.
  725: *
  726:          INDWKN = INDWK
  727:          LLWRKN = LWORK - INDWKN + 1
  728:          CALL ZUNMTR( 'L', UPLO, 'N', N, M, A, LDA, WORK( INDTAU ), Z,
  729:      $                LDZ, WORK( INDWKN ), LLWRKN, IINFO )
  730:       END IF
  731: *
  732: *     If matrix was scaled, then rescale eigenvalues appropriately.
  733: *
  734:    30 CONTINUE
  735:       IF( ISCALE.EQ.1 ) THEN
  736:          IF( INFO.EQ.0 ) THEN
  737:             IMAX = M
  738:          ELSE
  739:             IMAX = INFO - 1
  740:          END IF
  741:          CALL DSCAL( IMAX, ONE / SIGMA, W, 1 )
  742:       END IF
  743: *
  744: *     If eigenvalues are not in order, then sort them, along with
  745: *     eigenvectors.
  746: *
  747:       IF( WANTZ ) THEN
  748:          DO 50 J = 1, M - 1
  749:             I = 0
  750:             TMP1 = W( J )
  751:             DO 40 JJ = J + 1, M
  752:                IF( W( JJ ).LT.TMP1 ) THEN
  753:                   I = JJ
  754:                   TMP1 = W( JJ )
  755:                END IF
  756:    40       CONTINUE
  757: *
  758:             IF( I.NE.0 ) THEN
  759:                ITMP1 = IWORK( INDIBL+I-1 )
  760:                W( I ) = W( J )
  761:                IWORK( INDIBL+I-1 ) = IWORK( INDIBL+J-1 )
  762:                W( J ) = TMP1
  763:                IWORK( INDIBL+J-1 ) = ITMP1
  764:                CALL ZSWAP( N, Z( 1, I ), 1, Z( 1, J ), 1 )
  765:             END IF
  766:    50    CONTINUE
  767:       END IF
  768: *
  769: *     Set WORK(1) to optimal workspace size.
  770: *
  771:       WORK( 1 )  = LWMIN
  772:       RWORK( 1 ) = LRWMIN
  773:       IWORK( 1 ) = LIWMIN
  774: *
  775:       RETURN
  776: *
  777: *     End of ZHEEVR_2STAGE
  778: *
  779:       END

CVSweb interface <joel.bertrand@systella.fr>