File:  [local] / rpl / lapack / lapack / dlarre.f
Revision 1.17: download - view: text, annotated - select for diffs - revision graph
Sat Aug 27 15:27:09 2016 UTC (7 years, 9 months ago) by bertrand
Branches: MAIN
CVS tags: HEAD

Mise à jour de lapack.

    1: *> \brief \b DLARRE given the tridiagonal matrix T, sets small off-diagonal elements to zero and for each unreduced block Ti, finds base representations and eigenvalues.
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at 
    6: *            http://www.netlib.org/lapack/explore-html/ 
    7: *
    8: *> \htmlonly
    9: *> Download DLARRE + dependencies 
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlarre.f"> 
   11: *> [TGZ]</a> 
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlarre.f"> 
   13: *> [ZIP]</a> 
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlarre.f"> 
   15: *> [TXT]</a>
   16: *> \endhtmlonly 
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *       SUBROUTINE DLARRE( RANGE, N, VL, VU, IL, IU, D, E, E2,
   22: *                           RTOL1, RTOL2, SPLTOL, NSPLIT, ISPLIT, M,
   23: *                           W, WERR, WGAP, IBLOCK, INDEXW, GERS, PIVMIN,
   24: *                           WORK, IWORK, INFO )
   25:    26: *       .. Scalar Arguments ..
   27: *       CHARACTER          RANGE
   28: *       INTEGER            IL, INFO, IU, M, N, NSPLIT
   29: *       DOUBLE PRECISION  PIVMIN, RTOL1, RTOL2, SPLTOL, VL, VU
   30: *       ..
   31: *       .. Array Arguments ..
   32: *       INTEGER            IBLOCK( * ), ISPLIT( * ), IWORK( * ),
   33: *      $                   INDEXW( * )
   34: *       DOUBLE PRECISION   D( * ), E( * ), E2( * ), GERS( * ),
   35: *      $                   W( * ),WERR( * ), WGAP( * ), WORK( * )
   36: *       ..
   37: *  
   38: *
   39: *> \par Purpose:
   40: *  =============
   41: *>
   42: *> \verbatim
   43: *>
   44: *> To find the desired eigenvalues of a given real symmetric
   45: *> tridiagonal matrix T, DLARRE sets any "small" off-diagonal
   46: *> elements to zero, and for each unreduced block T_i, it finds
   47: *> (a) a suitable shift at one end of the block's spectrum,
   48: *> (b) the base representation, T_i - sigma_i I = L_i D_i L_i^T, and
   49: *> (c) eigenvalues of each L_i D_i L_i^T.
   50: *> The representations and eigenvalues found are then used by
   51: *> DSTEMR to compute the eigenvectors of T.
   52: *> The accuracy varies depending on whether bisection is used to
   53: *> find a few eigenvalues or the dqds algorithm (subroutine DLASQ2) to
   54: *> conpute all and then discard any unwanted one.
   55: *> As an added benefit, DLARRE also outputs the n
   56: *> Gerschgorin intervals for the matrices L_i D_i L_i^T.
   57: *> \endverbatim
   58: *
   59: *  Arguments:
   60: *  ==========
   61: *
   62: *> \param[in] RANGE
   63: *> \verbatim
   64: *>          RANGE is CHARACTER*1
   65: *>          = 'A': ("All")   all eigenvalues will be found.
   66: *>          = 'V': ("Value") all eigenvalues in the half-open interval
   67: *>                           (VL, VU] will be found.
   68: *>          = 'I': ("Index") the IL-th through IU-th eigenvalues (of the
   69: *>                           entire matrix) will be found.
   70: *> \endverbatim
   71: *>
   72: *> \param[in] N
   73: *> \verbatim
   74: *>          N is INTEGER
   75: *>          The order of the matrix. N > 0.
   76: *> \endverbatim
   77: *>
   78: *> \param[in,out] VL
   79: *> \verbatim
   80: *>          VL is DOUBLE PRECISION
   81: *>          If RANGE='V', the lower bound for the eigenvalues.
   82: *>          Eigenvalues less than or equal to VL, or greater than VU,
   83: *>          will not be returned.  VL < VU.
   84: *>          If RANGE='I' or ='A', DLARRE computes bounds on the desired
   85: *>          part of the spectrum.
   86: *> \endverbatim
   87: *>
   88: *> \param[in,out] VU
   89: *> \verbatim
   90: *>          VU is DOUBLE PRECISION
   91: *>          If RANGE='V', the upper bound for the eigenvalues.
   92: *>          Eigenvalues less than or equal to VL, or greater than VU,
   93: *>          will not be returned.  VL < VU.
   94: *>          If RANGE='I' or ='A', DLARRE computes bounds on the desired
   95: *>          part of the spectrum.
   96: *> \endverbatim
   97: *>
   98: *> \param[in] IL
   99: *> \verbatim
  100: *>          IL is INTEGER
  101: *>          If RANGE='I', the index of the
  102: *>          smallest eigenvalue to be returned.
  103: *>          1 <= IL <= IU <= N.
  104: *> \endverbatim
  105: *>
  106: *> \param[in] IU
  107: *> \verbatim
  108: *>          IU is INTEGER
  109: *>          If RANGE='I', the index of the
  110: *>          largest eigenvalue to be returned.
  111: *>          1 <= IL <= IU <= N.
  112: *> \endverbatim
  113: *>
  114: *> \param[in,out] D
  115: *> \verbatim
  116: *>          D is DOUBLE PRECISION array, dimension (N)
  117: *>          On entry, the N diagonal elements of the tridiagonal
  118: *>          matrix T.
  119: *>          On exit, the N diagonal elements of the diagonal
  120: *>          matrices D_i.
  121: *> \endverbatim
  122: *>
  123: *> \param[in,out] E
  124: *> \verbatim
  125: *>          E is DOUBLE PRECISION array, dimension (N)
  126: *>          On entry, the first (N-1) entries contain the subdiagonal
  127: *>          elements of the tridiagonal matrix T; E(N) need not be set.
  128: *>          On exit, E contains the subdiagonal elements of the unit
  129: *>          bidiagonal matrices L_i. The entries E( ISPLIT( I ) ),
  130: *>          1 <= I <= NSPLIT, contain the base points sigma_i on output.
  131: *> \endverbatim
  132: *>
  133: *> \param[in,out] E2
  134: *> \verbatim
  135: *>          E2 is DOUBLE PRECISION array, dimension (N)
  136: *>          On entry, the first (N-1) entries contain the SQUARES of the
  137: *>          subdiagonal elements of the tridiagonal matrix T;
  138: *>          E2(N) need not be set.
  139: *>          On exit, the entries E2( ISPLIT( I ) ),
  140: *>          1 <= I <= NSPLIT, have been set to zero
  141: *> \endverbatim
  142: *>
  143: *> \param[in] RTOL1
  144: *> \verbatim
  145: *>          RTOL1 is DOUBLE PRECISION
  146: *> \endverbatim
  147: *>
  148: *> \param[in] RTOL2
  149: *> \verbatim
  150: *>          RTOL2 is DOUBLE PRECISION
  151: *>           Parameters for bisection.
  152: *>           An interval [LEFT,RIGHT] has converged if
  153: *>           RIGHT-LEFT.LT.MAX( RTOL1*GAP, RTOL2*MAX(|LEFT|,|RIGHT|) )
  154: *> \endverbatim
  155: *>
  156: *> \param[in] SPLTOL
  157: *> \verbatim
  158: *>          SPLTOL is DOUBLE PRECISION
  159: *>          The threshold for splitting.
  160: *> \endverbatim
  161: *>
  162: *> \param[out] NSPLIT
  163: *> \verbatim
  164: *>          NSPLIT is INTEGER
  165: *>          The number of blocks T splits into. 1 <= NSPLIT <= N.
  166: *> \endverbatim
  167: *>
  168: *> \param[out] ISPLIT
  169: *> \verbatim
  170: *>          ISPLIT is INTEGER array, dimension (N)
  171: *>          The splitting points, at which T breaks up into blocks.
  172: *>          The first block consists of rows/columns 1 to ISPLIT(1),
  173: *>          the second of rows/columns ISPLIT(1)+1 through ISPLIT(2),
  174: *>          etc., and the NSPLIT-th consists of rows/columns
  175: *>          ISPLIT(NSPLIT-1)+1 through ISPLIT(NSPLIT)=N.
  176: *> \endverbatim
  177: *>
  178: *> \param[out] M
  179: *> \verbatim
  180: *>          M is INTEGER
  181: *>          The total number of eigenvalues (of all L_i D_i L_i^T)
  182: *>          found.
  183: *> \endverbatim
  184: *>
  185: *> \param[out] W
  186: *> \verbatim
  187: *>          W is DOUBLE PRECISION array, dimension (N)
  188: *>          The first M elements contain the eigenvalues. The
  189: *>          eigenvalues of each of the blocks, L_i D_i L_i^T, are
  190: *>          sorted in ascending order ( DLARRE may use the
  191: *>          remaining N-M elements as workspace).
  192: *> \endverbatim
  193: *>
  194: *> \param[out] WERR
  195: *> \verbatim
  196: *>          WERR is DOUBLE PRECISION array, dimension (N)
  197: *>          The error bound on the corresponding eigenvalue in W.
  198: *> \endverbatim
  199: *>
  200: *> \param[out] WGAP
  201: *> \verbatim
  202: *>          WGAP is DOUBLE PRECISION array, dimension (N)
  203: *>          The separation from the right neighbor eigenvalue in W.
  204: *>          The gap is only with respect to the eigenvalues of the same block
  205: *>          as each block has its own representation tree.
  206: *>          Exception: at the right end of a block we store the left gap
  207: *> \endverbatim
  208: *>
  209: *> \param[out] IBLOCK
  210: *> \verbatim
  211: *>          IBLOCK is INTEGER array, dimension (N)
  212: *>          The indices of the blocks (submatrices) associated with the
  213: *>          corresponding eigenvalues in W; IBLOCK(i)=1 if eigenvalue
  214: *>          W(i) belongs to the first block from the top, =2 if W(i)
  215: *>          belongs to the second block, etc.
  216: *> \endverbatim
  217: *>
  218: *> \param[out] INDEXW
  219: *> \verbatim
  220: *>          INDEXW is INTEGER array, dimension (N)
  221: *>          The indices of the eigenvalues within each block (submatrix);
  222: *>          for example, INDEXW(i)= 10 and IBLOCK(i)=2 imply that the
  223: *>          i-th eigenvalue W(i) is the 10-th eigenvalue in block 2
  224: *> \endverbatim
  225: *>
  226: *> \param[out] GERS
  227: *> \verbatim
  228: *>          GERS is DOUBLE PRECISION array, dimension (2*N)
  229: *>          The N Gerschgorin intervals (the i-th Gerschgorin interval
  230: *>          is (GERS(2*i-1), GERS(2*i)).
  231: *> \endverbatim
  232: *>
  233: *> \param[out] PIVMIN
  234: *> \verbatim
  235: *>          PIVMIN is DOUBLE PRECISION
  236: *>          The minimum pivot in the Sturm sequence for T.
  237: *> \endverbatim
  238: *>
  239: *> \param[out] WORK
  240: *> \verbatim
  241: *>          WORK is DOUBLE PRECISION array, dimension (6*N)
  242: *>          Workspace.
  243: *> \endverbatim
  244: *>
  245: *> \param[out] IWORK
  246: *> \verbatim
  247: *>          IWORK is INTEGER array, dimension (5*N)
  248: *>          Workspace.
  249: *> \endverbatim
  250: *>
  251: *> \param[out] INFO
  252: *> \verbatim
  253: *>          INFO is INTEGER
  254: *>          = 0:  successful exit
  255: *>          > 0:  A problem occurred in DLARRE.
  256: *>          < 0:  One of the called subroutines signaled an internal problem.
  257: *>                Needs inspection of the corresponding parameter IINFO
  258: *>                for further information.
  259: *>
  260: *>          =-1:  Problem in DLARRD.
  261: *>          = 2:  No base representation could be found in MAXTRY iterations.
  262: *>                Increasing MAXTRY and recompilation might be a remedy.
  263: *>          =-3:  Problem in DLARRB when computing the refined root
  264: *>                representation for DLASQ2.
  265: *>          =-4:  Problem in DLARRB when preforming bisection on the
  266: *>                desired part of the spectrum.
  267: *>          =-5:  Problem in DLASQ2.
  268: *>          =-6:  Problem in DLASQ2.
  269: *> \endverbatim
  270: *
  271: *  Authors:
  272: *  ========
  273: *
  274: *> \author Univ. of Tennessee 
  275: *> \author Univ. of California Berkeley 
  276: *> \author Univ. of Colorado Denver 
  277: *> \author NAG Ltd. 
  278: *
  279: *> \date June 2016
  280: *
  281: *> \ingroup auxOTHERauxiliary
  282: *
  283: *> \par Further Details:
  284: *  =====================
  285: *>
  286: *> \verbatim
  287: *>
  288: *>  The base representations are required to suffer very little
  289: *>  element growth and consequently define all their eigenvalues to
  290: *>  high relative accuracy.
  291: *> \endverbatim
  292: *
  293: *> \par Contributors:
  294: *  ==================
  295: *>
  296: *>     Beresford Parlett, University of California, Berkeley, USA \n
  297: *>     Jim Demmel, University of California, Berkeley, USA \n
  298: *>     Inderjit Dhillon, University of Texas, Austin, USA \n
  299: *>     Osni Marques, LBNL/NERSC, USA \n
  300: *>     Christof Voemel, University of California, Berkeley, USA \n
  301: *>
  302: *  =====================================================================
  303:       SUBROUTINE DLARRE( RANGE, N, VL, VU, IL, IU, D, E, E2,
  304:      $                    RTOL1, RTOL2, SPLTOL, NSPLIT, ISPLIT, M,
  305:      $                    W, WERR, WGAP, IBLOCK, INDEXW, GERS, PIVMIN,
  306:      $                    WORK, IWORK, INFO )
  307: *
  308: *  -- LAPACK auxiliary routine (version 3.6.1) --
  309: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
  310: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  311: *     June 2016
  312: *
  313: *     .. Scalar Arguments ..
  314:       CHARACTER          RANGE
  315:       INTEGER            IL, INFO, IU, M, N, NSPLIT
  316:       DOUBLE PRECISION  PIVMIN, RTOL1, RTOL2, SPLTOL, VL, VU
  317: *     ..
  318: *     .. Array Arguments ..
  319:       INTEGER            IBLOCK( * ), ISPLIT( * ), IWORK( * ),
  320:      $                   INDEXW( * )
  321:       DOUBLE PRECISION   D( * ), E( * ), E2( * ), GERS( * ),
  322:      $                   W( * ),WERR( * ), WGAP( * ), WORK( * )
  323: *     ..
  324: *
  325: *  =====================================================================
  326: *
  327: *     .. Parameters ..
  328:       DOUBLE PRECISION   FAC, FOUR, FOURTH, FUDGE, HALF, HNDRD,
  329:      $                   MAXGROWTH, ONE, PERT, TWO, ZERO
  330:       PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0,
  331:      $                     TWO = 2.0D0, FOUR=4.0D0,
  332:      $                     HNDRD = 100.0D0,
  333:      $                     PERT = 8.0D0,
  334:      $                     HALF = ONE/TWO, FOURTH = ONE/FOUR, FAC= HALF,
  335:      $                     MAXGROWTH = 64.0D0, FUDGE = 2.0D0 )
  336:       INTEGER            MAXTRY, ALLRNG, INDRNG, VALRNG
  337:       PARAMETER          ( MAXTRY = 6, ALLRNG = 1, INDRNG = 2,
  338:      $                     VALRNG = 3 )
  339: *     ..
  340: *     .. Local Scalars ..
  341:       LOGICAL            FORCEB, NOREP, USEDQD
  342:       INTEGER            CNT, CNT1, CNT2, I, IBEGIN, IDUM, IEND, IINFO,
  343:      $                   IN, INDL, INDU, IRANGE, J, JBLK, MB, MM,
  344:      $                   WBEGIN, WEND
  345:       DOUBLE PRECISION   AVGAP, BSRTOL, CLWDTH, DMAX, DPIVOT, EABS,
  346:      $                   EMAX, EOLD, EPS, GL, GU, ISLEFT, ISRGHT, RTL,
  347:      $                   RTOL, S1, S2, SAFMIN, SGNDEF, SIGMA, SPDIAM,
  348:      $                   TAU, TMP, TMP1
  349: 
  350: 
  351: *     ..
  352: *     .. Local Arrays ..
  353:       INTEGER            ISEED( 4 )
  354: *     ..
  355: *     .. External Functions ..
  356:       LOGICAL            LSAME
  357:       DOUBLE PRECISION            DLAMCH
  358:       EXTERNAL           DLAMCH, LSAME
  359: 
  360: *     ..
  361: *     .. External Subroutines ..
  362:       EXTERNAL           DCOPY, DLARNV, DLARRA, DLARRB, DLARRC, DLARRD,
  363:      $                   DLASQ2
  364: *     ..
  365: *     .. Intrinsic Functions ..
  366:       INTRINSIC          ABS, MAX, MIN
  367: 
  368: *     ..
  369: *     .. Executable Statements ..
  370: *
  371: 
  372:       INFO = 0
  373: 
  374: *
  375: *     Decode RANGE
  376: *
  377:       IF( LSAME( RANGE, 'A' ) ) THEN
  378:          IRANGE = ALLRNG
  379:       ELSE IF( LSAME( RANGE, 'V' ) ) THEN
  380:          IRANGE = VALRNG
  381:       ELSE IF( LSAME( RANGE, 'I' ) ) THEN
  382:          IRANGE = INDRNG
  383:       END IF
  384: 
  385:       M = 0
  386: 
  387: *     Get machine constants
  388:       SAFMIN = DLAMCH( 'S' )
  389:       EPS = DLAMCH( 'P' )
  390: 
  391: *     Set parameters
  392:       RTL = SQRT(EPS)
  393:       BSRTOL = SQRT(EPS)
  394: 
  395: *     Treat case of 1x1 matrix for quick return
  396:       IF( N.EQ.1 ) THEN
  397:          IF( (IRANGE.EQ.ALLRNG).OR.
  398:      $       ((IRANGE.EQ.VALRNG).AND.(D(1).GT.VL).AND.(D(1).LE.VU)).OR.
  399:      $       ((IRANGE.EQ.INDRNG).AND.(IL.EQ.1).AND.(IU.EQ.1)) ) THEN
  400:             M = 1
  401:             W(1) = D(1)
  402: *           The computation error of the eigenvalue is zero
  403:             WERR(1) = ZERO
  404:             WGAP(1) = ZERO
  405:             IBLOCK( 1 ) = 1
  406:             INDEXW( 1 ) = 1
  407:             GERS(1) = D( 1 )
  408:             GERS(2) = D( 1 )
  409:          ENDIF
  410: *        store the shift for the initial RRR, which is zero in this case
  411:          E(1) = ZERO
  412:          RETURN
  413:       END IF
  414: 
  415: *     General case: tridiagonal matrix of order > 1
  416: *
  417: *     Init WERR, WGAP. Compute Gerschgorin intervals and spectral diameter.
  418: *     Compute maximum off-diagonal entry and pivmin.
  419:       GL = D(1)
  420:       GU = D(1)
  421:       EOLD = ZERO
  422:       EMAX = ZERO
  423:       E(N) = ZERO
  424:       DO 5 I = 1,N
  425:          WERR(I) = ZERO
  426:          WGAP(I) = ZERO
  427:          EABS = ABS( E(I) )
  428:          IF( EABS .GE. EMAX ) THEN
  429:             EMAX = EABS
  430:          END IF
  431:          TMP1 = EABS + EOLD
  432:          GERS( 2*I-1) = D(I) - TMP1
  433:          GL =  MIN( GL, GERS( 2*I - 1))
  434:          GERS( 2*I ) = D(I) + TMP1
  435:          GU = MAX( GU, GERS(2*I) )
  436:          EOLD  = EABS
  437:  5    CONTINUE
  438: *     The minimum pivot allowed in the Sturm sequence for T
  439:       PIVMIN = SAFMIN * MAX( ONE, EMAX**2 )
  440: *     Compute spectral diameter. The Gerschgorin bounds give an
  441: *     estimate that is wrong by at most a factor of SQRT(2)
  442:       SPDIAM = GU - GL
  443: 
  444: *     Compute splitting points
  445:       CALL DLARRA( N, D, E, E2, SPLTOL, SPDIAM,
  446:      $                    NSPLIT, ISPLIT, IINFO )
  447: 
  448: *     Can force use of bisection instead of faster DQDS.
  449: *     Option left in the code for future multisection work.
  450:       FORCEB = .FALSE.
  451: 
  452: *     Initialize USEDQD, DQDS should be used for ALLRNG unless someone
  453: *     explicitly wants bisection.
  454:       USEDQD = (( IRANGE.EQ.ALLRNG ) .AND. (.NOT.FORCEB))
  455: 
  456:       IF( (IRANGE.EQ.ALLRNG) .AND. (.NOT. FORCEB) ) THEN
  457: *        Set interval [VL,VU] that contains all eigenvalues
  458:          VL = GL
  459:          VU = GU
  460:       ELSE
  461: *        We call DLARRD to find crude approximations to the eigenvalues
  462: *        in the desired range. In case IRANGE = INDRNG, we also obtain the
  463: *        interval (VL,VU] that contains all the wanted eigenvalues.
  464: *        An interval [LEFT,RIGHT] has converged if
  465: *        RIGHT-LEFT.LT.RTOL*MAX(ABS(LEFT),ABS(RIGHT))
  466: *        DLARRD needs a WORK of size 4*N, IWORK of size 3*N
  467:          CALL DLARRD( RANGE, 'B', N, VL, VU, IL, IU, GERS,
  468:      $                    BSRTOL, D, E, E2, PIVMIN, NSPLIT, ISPLIT,
  469:      $                    MM, W, WERR, VL, VU, IBLOCK, INDEXW,
  470:      $                    WORK, IWORK, IINFO )
  471:          IF( IINFO.NE.0 ) THEN
  472:             INFO = -1
  473:             RETURN
  474:          ENDIF
  475: *        Make sure that the entries M+1 to N in W, WERR, IBLOCK, INDEXW are 0
  476:          DO 14 I = MM+1,N
  477:             W( I ) = ZERO
  478:             WERR( I ) = ZERO
  479:             IBLOCK( I ) = 0
  480:             INDEXW( I ) = 0
  481:  14      CONTINUE
  482:       END IF
  483: 
  484: 
  485: ***
  486: *     Loop over unreduced blocks
  487:       IBEGIN = 1
  488:       WBEGIN = 1
  489:       DO 170 JBLK = 1, NSPLIT
  490:          IEND = ISPLIT( JBLK )
  491:          IN = IEND - IBEGIN + 1
  492: 
  493: *        1 X 1 block
  494:          IF( IN.EQ.1 ) THEN
  495:             IF( (IRANGE.EQ.ALLRNG).OR.( (IRANGE.EQ.VALRNG).AND.
  496:      $         ( D( IBEGIN ).GT.VL ).AND.( D( IBEGIN ).LE.VU ) )
  497:      $        .OR. ( (IRANGE.EQ.INDRNG).AND.(IBLOCK(WBEGIN).EQ.JBLK))
  498:      $        ) THEN
  499:                M = M + 1
  500:                W( M ) = D( IBEGIN )
  501:                WERR(M) = ZERO
  502: *              The gap for a single block doesn't matter for the later
  503: *              algorithm and is assigned an arbitrary large value
  504:                WGAP(M) = ZERO
  505:                IBLOCK( M ) = JBLK
  506:                INDEXW( M ) = 1
  507:                WBEGIN = WBEGIN + 1
  508:             ENDIF
  509: *           E( IEND ) holds the shift for the initial RRR
  510:             E( IEND ) = ZERO
  511:             IBEGIN = IEND + 1
  512:             GO TO 170
  513:          END IF
  514: *
  515: *        Blocks of size larger than 1x1
  516: *
  517: *        E( IEND ) will hold the shift for the initial RRR, for now set it =0
  518:          E( IEND ) = ZERO
  519: *
  520: *        Find local outer bounds GL,GU for the block
  521:          GL = D(IBEGIN)
  522:          GU = D(IBEGIN)
  523:          DO 15 I = IBEGIN , IEND
  524:             GL = MIN( GERS( 2*I-1 ), GL )
  525:             GU = MAX( GERS( 2*I ), GU )
  526:  15      CONTINUE
  527:          SPDIAM = GU - GL
  528: 
  529:          IF(.NOT. ((IRANGE.EQ.ALLRNG).AND.(.NOT.FORCEB)) ) THEN
  530: *           Count the number of eigenvalues in the current block.
  531:             MB = 0
  532:             DO 20 I = WBEGIN,MM
  533:                IF( IBLOCK(I).EQ.JBLK ) THEN
  534:                   MB = MB+1
  535:                ELSE
  536:                   GOTO 21
  537:                ENDIF
  538:  20         CONTINUE
  539:  21         CONTINUE
  540: 
  541:             IF( MB.EQ.0) THEN
  542: *              No eigenvalue in the current block lies in the desired range
  543: *              E( IEND ) holds the shift for the initial RRR
  544:                E( IEND ) = ZERO
  545:                IBEGIN = IEND + 1
  546:                GO TO 170
  547:             ELSE
  548: 
  549: *              Decide whether dqds or bisection is more efficient
  550:                USEDQD = ( (MB .GT. FAC*IN) .AND. (.NOT.FORCEB) )
  551:                WEND = WBEGIN + MB - 1
  552: *              Calculate gaps for the current block
  553: *              In later stages, when representations for individual
  554: *              eigenvalues are different, we use SIGMA = E( IEND ).
  555:                SIGMA = ZERO
  556:                DO 30 I = WBEGIN, WEND - 1
  557:                   WGAP( I ) = MAX( ZERO,
  558:      $                        W(I+1)-WERR(I+1) - (W(I)+WERR(I)) )
  559:  30            CONTINUE
  560:                WGAP( WEND ) = MAX( ZERO,
  561:      $                     VU - SIGMA - (W( WEND )+WERR( WEND )))
  562: *              Find local index of the first and last desired evalue.
  563:                INDL = INDEXW(WBEGIN)
  564:                INDU = INDEXW( WEND )
  565:             ENDIF
  566:          ENDIF
  567:          IF(( (IRANGE.EQ.ALLRNG) .AND. (.NOT. FORCEB) ).OR.USEDQD) THEN
  568: *           Case of DQDS
  569: *           Find approximations to the extremal eigenvalues of the block
  570:             CALL DLARRK( IN, 1, GL, GU, D(IBEGIN),
  571:      $               E2(IBEGIN), PIVMIN, RTL, TMP, TMP1, IINFO )
  572:             IF( IINFO.NE.0 ) THEN
  573:                INFO = -1
  574:                RETURN
  575:             ENDIF
  576:             ISLEFT = MAX(GL, TMP - TMP1
  577:      $               - HNDRD * EPS* ABS(TMP - TMP1))
  578: 
  579:             CALL DLARRK( IN, IN, GL, GU, D(IBEGIN),
  580:      $               E2(IBEGIN), PIVMIN, RTL, TMP, TMP1, IINFO )
  581:             IF( IINFO.NE.0 ) THEN
  582:                INFO = -1
  583:                RETURN
  584:             ENDIF
  585:             ISRGHT = MIN(GU, TMP + TMP1
  586:      $                 + HNDRD * EPS * ABS(TMP + TMP1))
  587: *           Improve the estimate of the spectral diameter
  588:             SPDIAM = ISRGHT - ISLEFT
  589:          ELSE
  590: *           Case of bisection
  591: *           Find approximations to the wanted extremal eigenvalues
  592:             ISLEFT = MAX(GL, W(WBEGIN) - WERR(WBEGIN)
  593:      $                  - HNDRD * EPS*ABS(W(WBEGIN)- WERR(WBEGIN) ))
  594:             ISRGHT = MIN(GU,W(WEND) + WERR(WEND)
  595:      $                  + HNDRD * EPS * ABS(W(WEND)+ WERR(WEND)))
  596:          ENDIF
  597: 
  598: 
  599: *        Decide whether the base representation for the current block
  600: *        L_JBLK D_JBLK L_JBLK^T = T_JBLK - sigma_JBLK I
  601: *        should be on the left or the right end of the current block.
  602: *        The strategy is to shift to the end which is "more populated"
  603: *        Furthermore, decide whether to use DQDS for the computation of
  604: *        the eigenvalue approximations at the end of DLARRE or bisection.
  605: *        dqds is chosen if all eigenvalues are desired or the number of
  606: *        eigenvalues to be computed is large compared to the blocksize.
  607:          IF( ( IRANGE.EQ.ALLRNG ) .AND. (.NOT.FORCEB) ) THEN
  608: *           If all the eigenvalues have to be computed, we use dqd
  609:             USEDQD = .TRUE.
  610: *           INDL is the local index of the first eigenvalue to compute
  611:             INDL = 1
  612:             INDU = IN
  613: *           MB =  number of eigenvalues to compute
  614:             MB = IN
  615:             WEND = WBEGIN + MB - 1
  616: *           Define 1/4 and 3/4 points of the spectrum
  617:             S1 = ISLEFT + FOURTH * SPDIAM
  618:             S2 = ISRGHT - FOURTH * SPDIAM
  619:          ELSE
  620: *           DLARRD has computed IBLOCK and INDEXW for each eigenvalue
  621: *           approximation.
  622: *           choose sigma
  623:             IF( USEDQD ) THEN
  624:                S1 = ISLEFT + FOURTH * SPDIAM
  625:                S2 = ISRGHT - FOURTH * SPDIAM
  626:             ELSE
  627:                TMP = MIN(ISRGHT,VU) -  MAX(ISLEFT,VL)
  628:                S1 =  MAX(ISLEFT,VL) + FOURTH * TMP
  629:                S2 =  MIN(ISRGHT,VU) - FOURTH * TMP
  630:             ENDIF
  631:          ENDIF
  632: 
  633: *        Compute the negcount at the 1/4 and 3/4 points
  634:          IF(MB.GT.1) THEN
  635:             CALL DLARRC( 'T', IN, S1, S2, D(IBEGIN),
  636:      $                    E(IBEGIN), PIVMIN, CNT, CNT1, CNT2, IINFO)
  637:          ENDIF
  638: 
  639:          IF(MB.EQ.1) THEN
  640:             SIGMA = GL
  641:             SGNDEF = ONE
  642:          ELSEIF( CNT1 - INDL .GE. INDU - CNT2 ) THEN
  643:             IF( ( IRANGE.EQ.ALLRNG ) .AND. (.NOT.FORCEB) ) THEN
  644:                SIGMA = MAX(ISLEFT,GL)
  645:             ELSEIF( USEDQD ) THEN
  646: *              use Gerschgorin bound as shift to get pos def matrix
  647: *              for dqds
  648:                SIGMA = ISLEFT
  649:             ELSE
  650: *              use approximation of the first desired eigenvalue of the
  651: *              block as shift
  652:                SIGMA = MAX(ISLEFT,VL)
  653:             ENDIF
  654:             SGNDEF = ONE
  655:          ELSE
  656:             IF( ( IRANGE.EQ.ALLRNG ) .AND. (.NOT.FORCEB) ) THEN
  657:                SIGMA = MIN(ISRGHT,GU)
  658:             ELSEIF( USEDQD ) THEN
  659: *              use Gerschgorin bound as shift to get neg def matrix
  660: *              for dqds
  661:                SIGMA = ISRGHT
  662:             ELSE
  663: *              use approximation of the first desired eigenvalue of the
  664: *              block as shift
  665:                SIGMA = MIN(ISRGHT,VU)
  666:             ENDIF
  667:             SGNDEF = -ONE
  668:          ENDIF
  669: 
  670: 
  671: *        An initial SIGMA has been chosen that will be used for computing
  672: *        T - SIGMA I = L D L^T
  673: *        Define the increment TAU of the shift in case the initial shift
  674: *        needs to be refined to obtain a factorization with not too much
  675: *        element growth.
  676:          IF( USEDQD ) THEN
  677: *           The initial SIGMA was to the outer end of the spectrum
  678: *           the matrix is definite and we need not retreat.
  679:             TAU = SPDIAM*EPS*N + TWO*PIVMIN
  680:             TAU = MAX( TAU,TWO*EPS*ABS(SIGMA) )
  681:          ELSE
  682:             IF(MB.GT.1) THEN
  683:                CLWDTH = W(WEND) + WERR(WEND) - W(WBEGIN) - WERR(WBEGIN)
  684:                AVGAP = ABS(CLWDTH / DBLE(WEND-WBEGIN))
  685:                IF( SGNDEF.EQ.ONE ) THEN
  686:                   TAU = HALF*MAX(WGAP(WBEGIN),AVGAP)
  687:                   TAU = MAX(TAU,WERR(WBEGIN))
  688:                ELSE
  689:                   TAU = HALF*MAX(WGAP(WEND-1),AVGAP)
  690:                   TAU = MAX(TAU,WERR(WEND))
  691:                ENDIF
  692:             ELSE
  693:                TAU = WERR(WBEGIN)
  694:             ENDIF
  695:          ENDIF
  696: *
  697:          DO 80 IDUM = 1, MAXTRY
  698: *           Compute L D L^T factorization of tridiagonal matrix T - sigma I.
  699: *           Store D in WORK(1:IN), L in WORK(IN+1:2*IN), and reciprocals of
  700: *           pivots in WORK(2*IN+1:3*IN)
  701:             DPIVOT = D( IBEGIN ) - SIGMA
  702:             WORK( 1 ) = DPIVOT
  703:             DMAX = ABS( WORK(1) )
  704:             J = IBEGIN
  705:             DO 70 I = 1, IN - 1
  706:                WORK( 2*IN+I ) = ONE / WORK( I )
  707:                TMP = E( J )*WORK( 2*IN+I )
  708:                WORK( IN+I ) = TMP
  709:                DPIVOT = ( D( J+1 )-SIGMA ) - TMP*E( J )
  710:                WORK( I+1 ) = DPIVOT
  711:                DMAX = MAX( DMAX, ABS(DPIVOT) )
  712:                J = J + 1
  713:  70         CONTINUE
  714: *           check for element growth
  715:             IF( DMAX .GT. MAXGROWTH*SPDIAM ) THEN
  716:                NOREP = .TRUE.
  717:             ELSE
  718:                NOREP = .FALSE.
  719:             ENDIF
  720:             IF( USEDQD .AND. .NOT.NOREP ) THEN
  721: *              Ensure the definiteness of the representation
  722: *              All entries of D (of L D L^T) must have the same sign
  723:                DO 71 I = 1, IN
  724:                   TMP = SGNDEF*WORK( I )
  725:                   IF( TMP.LT.ZERO ) NOREP = .TRUE.
  726:  71            CONTINUE
  727:             ENDIF
  728:             IF(NOREP) THEN
  729: *              Note that in the case of IRANGE=ALLRNG, we use the Gerschgorin
  730: *              shift which makes the matrix definite. So we should end up
  731: *              here really only in the case of IRANGE = VALRNG or INDRNG.
  732:                IF( IDUM.EQ.MAXTRY-1 ) THEN
  733:                   IF( SGNDEF.EQ.ONE ) THEN
  734: *                    The fudged Gerschgorin shift should succeed
  735:                      SIGMA =
  736:      $                    GL - FUDGE*SPDIAM*EPS*N - FUDGE*TWO*PIVMIN
  737:                   ELSE
  738:                      SIGMA =
  739:      $                    GU + FUDGE*SPDIAM*EPS*N + FUDGE*TWO*PIVMIN
  740:                   END IF
  741:                ELSE
  742:                   SIGMA = SIGMA - SGNDEF * TAU
  743:                   TAU = TWO * TAU
  744:                END IF
  745:             ELSE
  746: *              an initial RRR is found
  747:                GO TO 83
  748:             END IF
  749:  80      CONTINUE
  750: *        if the program reaches this point, no base representation could be
  751: *        found in MAXTRY iterations.
  752:          INFO = 2
  753:          RETURN
  754: 
  755:  83      CONTINUE
  756: *        At this point, we have found an initial base representation
  757: *        T - SIGMA I = L D L^T with not too much element growth.
  758: *        Store the shift.
  759:          E( IEND ) = SIGMA
  760: *        Store D and L.
  761:          CALL DCOPY( IN, WORK, 1, D( IBEGIN ), 1 )
  762:          CALL DCOPY( IN-1, WORK( IN+1 ), 1, E( IBEGIN ), 1 )
  763: 
  764: 
  765:          IF(MB.GT.1 ) THEN
  766: *
  767: *           Perturb each entry of the base representation by a small
  768: *           (but random) relative amount to overcome difficulties with
  769: *           glued matrices.
  770: *
  771:             DO 122 I = 1, 4
  772:                ISEED( I ) = 1
  773:  122        CONTINUE
  774: 
  775:             CALL DLARNV(2, ISEED, 2*IN-1, WORK(1))
  776:             DO 125 I = 1,IN-1
  777:                D(IBEGIN+I-1) = D(IBEGIN+I-1)*(ONE+EPS*PERT*WORK(I))
  778:                E(IBEGIN+I-1) = E(IBEGIN+I-1)*(ONE+EPS*PERT*WORK(IN+I))
  779:  125        CONTINUE
  780:             D(IEND) = D(IEND)*(ONE+EPS*FOUR*WORK(IN))
  781: *
  782:          ENDIF
  783: *
  784: *        Don't update the Gerschgorin intervals because keeping track
  785: *        of the updates would be too much work in DLARRV.
  786: *        We update W instead and use it to locate the proper Gerschgorin
  787: *        intervals.
  788: 
  789: *        Compute the required eigenvalues of L D L' by bisection or dqds
  790:          IF ( .NOT.USEDQD ) THEN
  791: *           If DLARRD has been used, shift the eigenvalue approximations
  792: *           according to their representation. This is necessary for
  793: *           a uniform DLARRV since dqds computes eigenvalues of the
  794: *           shifted representation. In DLARRV, W will always hold the
  795: *           UNshifted eigenvalue approximation.
  796:             DO 134 J=WBEGIN,WEND
  797:                W(J) = W(J) - SIGMA
  798:                WERR(J) = WERR(J) + ABS(W(J)) * EPS
  799:  134        CONTINUE
  800: *           call DLARRB to reduce eigenvalue error of the approximations
  801: *           from DLARRD
  802:             DO 135 I = IBEGIN, IEND-1
  803:                WORK( I ) = D( I ) * E( I )**2
  804:  135        CONTINUE
  805: *           use bisection to find EV from INDL to INDU
  806:             CALL DLARRB(IN, D(IBEGIN), WORK(IBEGIN),
  807:      $                  INDL, INDU, RTOL1, RTOL2, INDL-1,
  808:      $                  W(WBEGIN), WGAP(WBEGIN), WERR(WBEGIN),
  809:      $                  WORK( 2*N+1 ), IWORK, PIVMIN, SPDIAM,
  810:      $                  IN, IINFO )
  811:             IF( IINFO .NE. 0 ) THEN
  812:                INFO = -4
  813:                RETURN
  814:             END IF
  815: *           DLARRB computes all gaps correctly except for the last one
  816: *           Record distance to VU/GU
  817:             WGAP( WEND ) = MAX( ZERO,
  818:      $           ( VU-SIGMA ) - ( W( WEND ) + WERR( WEND ) ) )
  819:             DO 138 I = INDL, INDU
  820:                M = M + 1
  821:                IBLOCK(M) = JBLK
  822:                INDEXW(M) = I
  823:  138        CONTINUE
  824:          ELSE
  825: *           Call dqds to get all eigs (and then possibly delete unwanted
  826: *           eigenvalues).
  827: *           Note that dqds finds the eigenvalues of the L D L^T representation
  828: *           of T to high relative accuracy. High relative accuracy
  829: *           might be lost when the shift of the RRR is subtracted to obtain
  830: *           the eigenvalues of T. However, T is not guaranteed to define its
  831: *           eigenvalues to high relative accuracy anyway.
  832: *           Set RTOL to the order of the tolerance used in DLASQ2
  833: *           This is an ESTIMATED error, the worst case bound is 4*N*EPS
  834: *           which is usually too large and requires unnecessary work to be
  835: *           done by bisection when computing the eigenvectors
  836:             RTOL = LOG(DBLE(IN)) * FOUR * EPS
  837:             J = IBEGIN
  838:             DO 140 I = 1, IN - 1
  839:                WORK( 2*I-1 ) = ABS( D( J ) )
  840:                WORK( 2*I ) = E( J )*E( J )*WORK( 2*I-1 )
  841:                J = J + 1
  842:   140       CONTINUE
  843:             WORK( 2*IN-1 ) = ABS( D( IEND ) )
  844:             WORK( 2*IN ) = ZERO
  845:             CALL DLASQ2( IN, WORK, IINFO )
  846:             IF( IINFO .NE. 0 ) THEN
  847: *              If IINFO = -5 then an index is part of a tight cluster
  848: *              and should be changed. The index is in IWORK(1) and the
  849: *              gap is in WORK(N+1)
  850:                INFO = -5
  851:                RETURN
  852:             ELSE
  853: *              Test that all eigenvalues are positive as expected
  854:                DO 149 I = 1, IN
  855:                   IF( WORK( I ).LT.ZERO ) THEN
  856:                      INFO = -6
  857:                      RETURN
  858:                   ENDIF
  859:  149           CONTINUE
  860:             END IF
  861:             IF( SGNDEF.GT.ZERO ) THEN
  862:                DO 150 I = INDL, INDU
  863:                   M = M + 1
  864:                   W( M ) = WORK( IN-I+1 )
  865:                   IBLOCK( M ) = JBLK
  866:                   INDEXW( M ) = I
  867:  150           CONTINUE
  868:             ELSE
  869:                DO 160 I = INDL, INDU
  870:                   M = M + 1
  871:                   W( M ) = -WORK( I )
  872:                   IBLOCK( M ) = JBLK
  873:                   INDEXW( M ) = I
  874:  160           CONTINUE
  875:             END IF
  876: 
  877:             DO 165 I = M - MB + 1, M
  878: *              the value of RTOL below should be the tolerance in DLASQ2
  879:                WERR( I ) = RTOL * ABS( W(I) )
  880:  165        CONTINUE
  881:             DO 166 I = M - MB + 1, M - 1
  882: *              compute the right gap between the intervals
  883:                WGAP( I ) = MAX( ZERO,
  884:      $                          W(I+1)-WERR(I+1) - (W(I)+WERR(I)) )
  885:  166        CONTINUE
  886:             WGAP( M ) = MAX( ZERO,
  887:      $           ( VU-SIGMA ) - ( W( M ) + WERR( M ) ) )
  888:          END IF
  889: *        proceed with next block
  890:          IBEGIN = IEND + 1
  891:          WBEGIN = WEND + 1
  892:  170  CONTINUE
  893: *
  894: 
  895:       RETURN
  896: *
  897: *     end of DLARRE
  898: *
  899:       END

CVSweb interface <joel.bertrand@systella.fr>