File:  [local] / rpl / lapack / lapack / zlaqz0.f
Revision 1.1: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:55:31 2023 UTC (9 months, 1 week ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Ajout de fichiers de lapack 3.11

    1: *> \brief \b ZLAQZ0
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *> \htmlonly
    9: *> Download ZLAQZ0 + dependencies
   10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlaqz0.f">
   11: *> [TGZ]</a>
   12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlaqz0.f">
   13: *> [ZIP]</a>
   14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlaqz0.f">
   15: *> [TXT]</a>
   16: *> \endhtmlonly
   17: *
   18: *  Definition:
   19: *  ===========
   20: *
   21: *      SUBROUTINE ZLAQZ0( WANTS, WANTQ, WANTZ, N, ILO, IHI, A, LDA, B,
   22: *     $    LDB, ALPHA, BETA, Q, LDQ, Z, LDZ, WORK, LWORK, RWORK, REC,
   23: *     $    INFO )
   24: *      IMPLICIT NONE
   25: *
   26: *      Arguments
   27: *      CHARACTER, INTENT( IN ) :: WANTS, WANTQ, WANTZ
   28: *      INTEGER, INTENT( IN ) :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, LWORK,
   29: *     $    REC
   30: *      INTEGER, INTENT( OUT ) :: INFO
   31: *      COMPLEX*16, INTENT( INOUT ) :: A( LDA, * ), B( LDB, * ), Q( LDQ,
   32: *     $    * ), Z( LDZ, * ), ALPHA( * ), BETA( * ), WORK( * )
   33: *      DOUBLE PRECISION, INTENT( OUT ) :: RWORK( * )
   34: *       ..
   35: *
   36: *
   37: *> \par Purpose:
   38: *  =============
   39: *>
   40: *> \verbatim
   41: *>
   42: *> ZLAQZ0 computes the eigenvalues of a real matrix pair (H,T),
   43: *> where H is an upper Hessenberg matrix and T is upper triangular,
   44: *> using the double-shift QZ method.
   45: *> Matrix pairs of this type are produced by the reduction to
   46: *> generalized upper Hessenberg form of a real matrix pair (A,B):
   47: *>
   48: *>    A = Q1*H*Z1**H,  B = Q1*T*Z1**H,
   49: *>
   50: *> as computed by ZGGHRD.
   51: *>
   52: *> If JOB='S', then the Hessenberg-triangular pair (H,T) is
   53: *> also reduced to generalized Schur form,
   54: *>
   55: *>    H = Q*S*Z**H,  T = Q*P*Z**H,
   56: *>
   57: *> where Q and Z are unitary matrices, P and S are an upper triangular
   58: *> matrices.
   59: *>
   60: *> Optionally, the unitary matrix Q from the generalized Schur
   61: *> factorization may be postmultiplied into an input matrix Q1, and the
   62: *> unitary matrix Z may be postmultiplied into an input matrix Z1.
   63: *> If Q1 and Z1 are the unitary matrices from ZGGHRD that reduced
   64: *> the matrix pair (A,B) to generalized upper Hessenberg form, then the
   65: *> output matrices Q1*Q and Z1*Z are the unitary factors from the
   66: *> generalized Schur factorization of (A,B):
   67: *>
   68: *>    A = (Q1*Q)*S*(Z1*Z)**H,  B = (Q1*Q)*P*(Z1*Z)**H.
   69: *>
   70: *> To avoid overflow, eigenvalues of the matrix pair (H,T) (equivalently,
   71: *> of (A,B)) are computed as a pair of values (alpha,beta), where alpha is
   72: *> complex and beta real.
   73: *> If beta is nonzero, lambda = alpha / beta is an eigenvalue of the
   74: *> generalized nonsymmetric eigenvalue problem (GNEP)
   75: *>    A*x = lambda*B*x
   76: *> and if alpha is nonzero, mu = beta / alpha is an eigenvalue of the
   77: *> alternate form of the GNEP
   78: *>    mu*A*y = B*y.
   79: *> Eigenvalues can be read directly from the generalized Schur
   80: *> form:
   81: *>   alpha = S(i,i), beta = P(i,i).
   82: *>
   83: *> Ref: C.B. Moler & G.W. Stewart, "An Algorithm for Generalized Matrix
   84: *>      Eigenvalue Problems", SIAM J. Numer. Anal., 10(1973),
   85: *>      pp. 241--256.
   86: *>
   87: *> Ref: B. Kagstrom, D. Kressner, "Multishift Variants of the QZ
   88: *>      Algorithm with Aggressive Early Deflation", SIAM J. Numer.
   89: *>      Anal., 29(2006), pp. 199--227.
   90: *>
   91: *> Ref: T. Steel, D. Camps, K. Meerbergen, R. Vandebril "A multishift,
   92: *>      multipole rational QZ method with agressive early deflation"
   93: *> \endverbatim
   94: *
   95: *  Arguments:
   96: *  ==========
   97: *
   98: *> \param[in] WANTS
   99: *> \verbatim
  100: *>          WANTS is CHARACTER*1
  101: *>          = 'E': Compute eigenvalues only;
  102: *>          = 'S': Compute eigenvalues and the Schur form.
  103: *> \endverbatim
  104: *>
  105: *> \param[in] WANTQ
  106: *> \verbatim
  107: *>          WANTQ is CHARACTER*1
  108: *>          = 'N': Left Schur vectors (Q) are not computed;
  109: *>          = 'I': Q is initialized to the unit matrix and the matrix Q
  110: *>                 of left Schur vectors of (A,B) is returned;
  111: *>          = 'V': Q must contain an unitary matrix Q1 on entry and
  112: *>                 the product Q1*Q is returned.
  113: *> \endverbatim
  114: *>
  115: *> \param[in] WANTZ
  116: *> \verbatim
  117: *>          WANTZ is CHARACTER*1
  118: *>          = 'N': Right Schur vectors (Z) are not computed;
  119: *>          = 'I': Z is initialized to the unit matrix and the matrix Z
  120: *>                 of right Schur vectors of (A,B) is returned;
  121: *>          = 'V': Z must contain an unitary matrix Z1 on entry and
  122: *>                 the product Z1*Z is returned.
  123: *> \endverbatim
  124: *>
  125: *> \param[in] N
  126: *> \verbatim
  127: *>          N is INTEGER
  128: *>          The order of the matrices A, B, Q, and Z.  N >= 0.
  129: *> \endverbatim
  130: *>
  131: *> \param[in] ILO
  132: *> \verbatim
  133: *>          ILO is INTEGER
  134: *> \endverbatim
  135: *>
  136: *> \param[in] IHI
  137: *> \verbatim
  138: *>          IHI is INTEGER
  139: *>          ILO and IHI mark the rows and columns of A which are in
  140: *>          Hessenberg form.  It is assumed that A is already upper
  141: *>          triangular in rows and columns 1:ILO-1 and IHI+1:N.
  142: *>          If N > 0, 1 <= ILO <= IHI <= N; if N = 0, ILO=1 and IHI=0.
  143: *> \endverbatim
  144: *>
  145: *> \param[in,out] A
  146: *> \verbatim
  147: *>          A is COMPLEX*16 array, dimension (LDA, N)
  148: *>          On entry, the N-by-N upper Hessenberg matrix A.
  149: *>          On exit, if JOB = 'S', A contains the upper triangular
  150: *>          matrix S from the generalized Schur factorization.
  151: *>          If JOB = 'E', the diagonal blocks of A match those of S, but
  152: *>          the rest of A is unspecified.
  153: *> \endverbatim
  154: *>
  155: *> \param[in] LDA
  156: *> \verbatim
  157: *>          LDA is INTEGER
  158: *>          The leading dimension of the array A.  LDA >= max( 1, N ).
  159: *> \endverbatim
  160: *>
  161: *> \param[in,out] B
  162: *> \verbatim
  163: *>          B is COMPLEX*16 array, dimension (LDB, N)
  164: *>          On entry, the N-by-N upper triangular matrix B.
  165: *>          On exit, if JOB = 'S', B contains the upper triangular
  166: *>          matrix P from the generalized Schur factorization;
  167: *>          If JOB = 'E', the diagonal blocks of B match those of P, but
  168: *>          the rest of B is unspecified.
  169: *> \endverbatim
  170: *>
  171: *> \param[in] LDB
  172: *> \verbatim
  173: *>          LDB is INTEGER
  174: *>          The leading dimension of the array B.  LDB >= max( 1, N ).
  175: *> \endverbatim
  176: *>
  177: *> \param[out] ALPHA
  178: *> \verbatim
  179: *>          ALPHA is COMPLEX*16 array, dimension (N)
  180: *>          Each scalar alpha defining an eigenvalue
  181: *>          of GNEP.
  182: *> \endverbatim
  183: *>
  184: *> \param[out] BETA
  185: *> \verbatim
  186: *>          BETA is COMPLEX*16 array, dimension (N)
  187: *>          The scalars beta that define the eigenvalues of GNEP.
  188: *>          Together, the quantities alpha = ALPHA(j) and
  189: *>          beta = BETA(j) represent the j-th eigenvalue of the matrix
  190: *>          pair (A,B), in one of the forms lambda = alpha/beta or
  191: *>          mu = beta/alpha.  Since either lambda or mu may overflow,
  192: *>          they should not, in general, be computed.
  193: *> \endverbatim
  194: *>
  195: *> \param[in,out] Q
  196: *> \verbatim
  197: *>          Q is COMPLEX*16 array, dimension (LDQ, N)
  198: *>          On entry, if COMPQ = 'V', the unitary matrix Q1 used in
  199: *>          the reduction of (A,B) to generalized Hessenberg form.
  200: *>          On exit, if COMPQ = 'I', the unitary matrix of left Schur
  201: *>          vectors of (A,B), and if COMPQ = 'V', the unitary matrix
  202: *>          of left Schur vectors of (A,B).
  203: *>          Not referenced if COMPQ = 'N'.
  204: *> \endverbatim
  205: *>
  206: *> \param[in] LDQ
  207: *> \verbatim
  208: *>          LDQ is INTEGER
  209: *>          The leading dimension of the array Q.  LDQ >= 1.
  210: *>          If COMPQ='V' or 'I', then LDQ >= N.
  211: *> \endverbatim
  212: *>
  213: *> \param[in,out] Z
  214: *> \verbatim
  215: *>          Z is COMPLEX*16 array, dimension (LDZ, N)
  216: *>          On entry, if COMPZ = 'V', the unitary matrix Z1 used in
  217: *>          the reduction of (A,B) to generalized Hessenberg form.
  218: *>          On exit, if COMPZ = 'I', the unitary matrix of
  219: *>          right Schur vectors of (H,T), and if COMPZ = 'V', the
  220: *>          unitary matrix of right Schur vectors of (A,B).
  221: *>          Not referenced if COMPZ = 'N'.
  222: *> \endverbatim
  223: *>
  224: *> \param[in] LDZ
  225: *> \verbatim
  226: *>          LDZ is INTEGER
  227: *>          The leading dimension of the array Z.  LDZ >= 1.
  228: *>          If COMPZ='V' or 'I', then LDZ >= N.
  229: *> \endverbatim
  230: *>
  231: *> \param[out] WORK
  232: *> \verbatim
  233: *>          WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
  234: *>          On exit, if INFO >= 0, WORK(1) returns the optimal LWORK.
  235: *> \endverbatim
  236: *>
  237: *> \param[out] RWORK
  238: *> \verbatim
  239: *>          RWORK is DOUBLE PRECISION array, dimension (N)
  240: *> \endverbatim
  241: *>
  242: *> \param[in] LWORK
  243: *> \verbatim
  244: *>          LWORK is INTEGER
  245: *>          The dimension of the array WORK.  LWORK >= max(1,N).
  246: *>
  247: *>          If LWORK = -1, then a workspace query is assumed; the routine
  248: *>          only calculates the optimal size of the WORK array, returns
  249: *>          this value as the first entry of the WORK array, and no error
  250: *>          message related to LWORK is issued by XERBLA.
  251: *> \endverbatim
  252: *>
  253: *> \param[in] REC
  254: *> \verbatim
  255: *>          REC is INTEGER
  256: *>             REC indicates the current recursion level. Should be set
  257: *>             to 0 on first call.
  258: *> \endverbatim
  259: *>
  260: *> \param[out] INFO
  261: *> \verbatim
  262: *>          INFO is INTEGER
  263: *>          = 0: successful exit
  264: *>          < 0: if INFO = -i, the i-th argument had an illegal value
  265: *>          = 1,...,N: the QZ iteration did not converge.  (A,B) is not
  266: *>                     in Schur form, but ALPHA(i) and
  267: *>                     BETA(i), i=INFO+1,...,N should be correct.
  268: *> \endverbatim
  269: *
  270: *  Authors:
  271: *  ========
  272: *
  273: *> \author Thijs Steel, KU Leuven
  274: *
  275: *> \date May 2020
  276: *
  277: *> \ingroup complex16GEcomputational
  278: *>
  279: *  =====================================================================
  280:       RECURSIVE SUBROUTINE ZLAQZ0( WANTS, WANTQ, WANTZ, N, ILO, IHI, A,
  281:      $                             LDA, B, LDB, ALPHA, BETA, Q, LDQ, Z,
  282:      $                             LDZ, WORK, LWORK, RWORK, REC,
  283:      $                             INFO )
  284:       IMPLICIT NONE
  285: 
  286: *     Arguments
  287:       CHARACTER, INTENT( IN ) :: WANTS, WANTQ, WANTZ
  288:       INTEGER, INTENT( IN ) :: N, ILO, IHI, LDA, LDB, LDQ, LDZ, LWORK,
  289:      $         REC
  290:       INTEGER, INTENT( OUT ) :: INFO
  291:       COMPLEX*16, INTENT( INOUT ) :: A( LDA, * ), B( LDB, * ), Q( LDQ,
  292:      $   * ), Z( LDZ, * ), ALPHA( * ), BETA( * ), WORK( * )
  293:       DOUBLE PRECISION, INTENT( OUT ) :: RWORK( * )
  294: 
  295: *     Parameters
  296:       COMPLEX*16         CZERO, CONE
  297:       PARAMETER          ( CZERO = ( 0.0D+0, 0.0D+0 ), CONE = ( 1.0D+0,
  298:      $                     0.0D+0 ) )
  299:       DOUBLE PRECISION :: ZERO, ONE, HALF
  300:       PARAMETER( ZERO = 0.0D0, ONE = 1.0D0, HALF = 0.5D0 )
  301: 
  302: *     Local scalars
  303:       DOUBLE PRECISION :: SMLNUM, ULP, SAFMIN, SAFMAX, C1, TEMPR,
  304:      $                    BNORM, BTOL
  305:       COMPLEX*16 :: ESHIFT, S1, TEMP
  306:       INTEGER :: ISTART, ISTOP, IITER, MAXIT, ISTART2, K, LD, NSHIFTS,
  307:      $           NBLOCK, NW, NMIN, NIBBLE, N_UNDEFLATED, N_DEFLATED,
  308:      $           NS, SWEEP_INFO, SHIFTPOS, LWORKREQ, K2, ISTARTM,
  309:      $           ISTOPM, IWANTS, IWANTQ, IWANTZ, NORM_INFO, AED_INFO,
  310:      $           NWR, NBR, NSR, ITEMP1, ITEMP2, RCOST
  311:       LOGICAL :: ILSCHUR, ILQ, ILZ
  312:       CHARACTER :: JBCMPZ*3
  313: 
  314: *     External Functions
  315:       EXTERNAL :: XERBLA, ZHGEQZ, ZLAQZ2, ZLAQZ3, ZLASET, DLABAD,
  316:      $            ZLARTG, ZROT
  317:       DOUBLE PRECISION, EXTERNAL :: DLAMCH, ZLANHS
  318:       LOGICAL, EXTERNAL :: LSAME
  319:       INTEGER, EXTERNAL :: ILAENV
  320: 
  321: *
  322: *     Decode wantS,wantQ,wantZ
  323: *      
  324:       IF( LSAME( WANTS, 'E' ) ) THEN
  325:          ILSCHUR = .FALSE.
  326:          IWANTS = 1
  327:       ELSE IF( LSAME( WANTS, 'S' ) ) THEN
  328:          ILSCHUR = .TRUE.
  329:          IWANTS = 2
  330:       ELSE
  331:          IWANTS = 0
  332:       END IF
  333: 
  334:       IF( LSAME( WANTQ, 'N' ) ) THEN
  335:          ILQ = .FALSE.
  336:          IWANTQ = 1
  337:       ELSE IF( LSAME( WANTQ, 'V' ) ) THEN
  338:          ILQ = .TRUE.
  339:          IWANTQ = 2
  340:       ELSE IF( LSAME( WANTQ, 'I' ) ) THEN
  341:          ILQ = .TRUE.
  342:          IWANTQ = 3
  343:       ELSE
  344:          IWANTQ = 0
  345:       END IF
  346: 
  347:       IF( LSAME( WANTZ, 'N' ) ) THEN
  348:          ILZ = .FALSE.
  349:          IWANTZ = 1
  350:       ELSE IF( LSAME( WANTZ, 'V' ) ) THEN
  351:          ILZ = .TRUE.
  352:          IWANTZ = 2
  353:       ELSE IF( LSAME( WANTZ, 'I' ) ) THEN
  354:          ILZ = .TRUE.
  355:          IWANTZ = 3
  356:       ELSE
  357:          IWANTZ = 0
  358:       END IF
  359: *
  360: *     Check Argument Values
  361: *
  362:       INFO = 0
  363:       IF( IWANTS.EQ.0 ) THEN
  364:          INFO = -1
  365:       ELSE IF( IWANTQ.EQ.0 ) THEN
  366:          INFO = -2
  367:       ELSE IF( IWANTZ.EQ.0 ) THEN
  368:          INFO = -3
  369:       ELSE IF( N.LT.0 ) THEN
  370:          INFO = -4
  371:       ELSE IF( ILO.LT.1 ) THEN
  372:          INFO = -5
  373:       ELSE IF( IHI.GT.N .OR. IHI.LT.ILO-1 ) THEN
  374:          INFO = -6
  375:       ELSE IF( LDA.LT.N ) THEN
  376:          INFO = -8
  377:       ELSE IF( LDB.LT.N ) THEN
  378:          INFO = -10
  379:       ELSE IF( LDQ.LT.1 .OR. ( ILQ .AND. LDQ.LT.N ) ) THEN
  380:          INFO = -15
  381:       ELSE IF( LDZ.LT.1 .OR. ( ILZ .AND. LDZ.LT.N ) ) THEN
  382:          INFO = -17
  383:       END IF
  384:       IF( INFO.NE.0 ) THEN
  385:          CALL XERBLA( 'ZLAQZ0', -INFO )
  386:          RETURN
  387:       END IF
  388:    
  389: *
  390: *     Quick return if possible
  391: *
  392:       IF( N.LE.0 ) THEN
  393:          WORK( 1 ) = DBLE( 1 )
  394:          RETURN
  395:       END IF
  396: 
  397: *
  398: *     Get the parameters
  399: *
  400:       JBCMPZ( 1:1 ) = WANTS
  401:       JBCMPZ( 2:2 ) = WANTQ
  402:       JBCMPZ( 3:3 ) = WANTZ
  403: 
  404:       NMIN = ILAENV( 12, 'ZLAQZ0', JBCMPZ, N, ILO, IHI, LWORK )
  405: 
  406:       NWR = ILAENV( 13, 'ZLAQZ0', JBCMPZ, N, ILO, IHI, LWORK )
  407:       NWR = MAX( 2, NWR )
  408:       NWR = MIN( IHI-ILO+1, ( N-1 ) / 3, NWR )
  409: 
  410:       NIBBLE = ILAENV( 14, 'ZLAQZ0', JBCMPZ, N, ILO, IHI, LWORK )
  411:       
  412:       NSR = ILAENV( 15, 'ZLAQZ0', JBCMPZ, N, ILO, IHI, LWORK )
  413:       NSR = MIN( NSR, ( N+6 ) / 9, IHI-ILO )
  414:       NSR = MAX( 2, NSR-MOD( NSR, 2 ) )
  415: 
  416:       RCOST = ILAENV( 17, 'ZLAQZ0', JBCMPZ, N, ILO, IHI, LWORK )
  417:       ITEMP1 = INT( NSR/SQRT( 1+2*NSR/( DBLE( RCOST )/100*N ) ) )
  418:       ITEMP1 = ( ( ITEMP1-1 )/4 )*4+4
  419:       NBR = NSR+ITEMP1
  420: 
  421:       IF( N .LT. NMIN .OR. REC .GE. 2 ) THEN
  422:          CALL ZHGEQZ( WANTS, WANTQ, WANTZ, N, ILO, IHI, A, LDA, B, LDB,
  423:      $                ALPHA, BETA, Q, LDQ, Z, LDZ, WORK, LWORK, RWORK,
  424:      $                INFO )
  425:          RETURN
  426:       END IF
  427: 
  428: *
  429: *     Find out required workspace
  430: *
  431: 
  432: *     Workspace query to ZLAQZ2
  433:       NW = MAX( NWR, NMIN )
  434:       CALL ZLAQZ2( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NW, A, LDA, B, LDB,
  435:      $             Q, LDQ, Z, LDZ, N_UNDEFLATED, N_DEFLATED, ALPHA,
  436:      $             BETA, WORK, NW, WORK, NW, WORK, -1, RWORK, REC,
  437:      $             AED_INFO )
  438:       ITEMP1 = INT( WORK( 1 ) )
  439: *     Workspace query to ZLAQZ3
  440:       CALL ZLAQZ3( ILSCHUR, ILQ, ILZ, N, ILO, IHI, NSR, NBR, ALPHA,
  441:      $             BETA, A, LDA, B, LDB, Q, LDQ, Z, LDZ, WORK, NBR,
  442:      $             WORK, NBR, WORK, -1, SWEEP_INFO )
  443:       ITEMP2 = INT( WORK( 1 ) )
  444: 
  445:       LWORKREQ = MAX( ITEMP1+2*NW**2, ITEMP2+2*NBR**2 )
  446:       IF ( LWORK .EQ.-1 ) THEN
  447:          WORK( 1 ) = DBLE( LWORKREQ )
  448:          RETURN
  449:       ELSE IF ( LWORK .LT. LWORKREQ ) THEN
  450:          INFO = -19
  451:       END IF
  452:       IF( INFO.NE.0 ) THEN
  453:          CALL XERBLA( 'ZLAQZ0', INFO )
  454:          RETURN
  455:       END IF
  456: *
  457: *     Initialize Q and Z
  458: *
  459:       IF( IWANTQ.EQ.3 ) CALL ZLASET( 'FULL', N, N, CZERO, CONE, Q,
  460:      $    LDQ )
  461:       IF( IWANTZ.EQ.3 ) CALL ZLASET( 'FULL', N, N, CZERO, CONE, Z,
  462:      $    LDZ )
  463: 
  464: *     Get machine constants
  465:       SAFMIN = DLAMCH( 'SAFE MINIMUM' )
  466:       SAFMAX = ONE/SAFMIN
  467:       CALL DLABAD( SAFMIN, SAFMAX )
  468:       ULP = DLAMCH( 'PRECISION' )
  469:       SMLNUM = SAFMIN*( DBLE( N )/ULP )
  470: 
  471:       BNORM = ZLANHS( 'F', IHI-ILO+1, B( ILO, ILO ), LDB, RWORK )
  472:       BTOL = MAX( SAFMIN, ULP*BNORM )
  473: 
  474:       ISTART = ILO
  475:       ISTOP = IHI
  476:       MAXIT = 30*( IHI-ILO+1 )
  477:       LD = 0
  478:  
  479:       DO IITER = 1, MAXIT
  480:          IF( IITER .GE. MAXIT ) THEN
  481:             INFO = ISTOP+1
  482:             GOTO 80
  483:          END IF
  484:          IF ( ISTART+1 .GE. ISTOP ) THEN
  485:             ISTOP = ISTART
  486:             EXIT
  487:          END IF
  488: 
  489: *        Check deflations at the end
  490:          IF ( ABS( A( ISTOP, ISTOP-1 ) ) .LE. MAX( SMLNUM,
  491:      $      ULP*( ABS( A( ISTOP, ISTOP ) )+ABS( A( ISTOP-1,
  492:      $      ISTOP-1 ) ) ) ) ) THEN
  493:             A( ISTOP, ISTOP-1 ) = CZERO
  494:             ISTOP = ISTOP-1
  495:             LD = 0
  496:             ESHIFT = CZERO
  497:          END IF
  498: *        Check deflations at the start
  499:          IF ( ABS( A( ISTART+1, ISTART ) ) .LE. MAX( SMLNUM,
  500:      $      ULP*( ABS( A( ISTART, ISTART ) )+ABS( A( ISTART+1,
  501:      $      ISTART+1 ) ) ) ) ) THEN
  502:             A( ISTART+1, ISTART ) = CZERO
  503:             ISTART = ISTART+1
  504:             LD = 0
  505:             ESHIFT = CZERO
  506:          END IF
  507: 
  508:          IF ( ISTART+1 .GE. ISTOP ) THEN
  509:             EXIT
  510:          END IF
  511: 
  512: *        Check interior deflations
  513:          ISTART2 = ISTART
  514:          DO K = ISTOP, ISTART+1, -1
  515:             IF ( ABS( A( K, K-1 ) ) .LE. MAX( SMLNUM, ULP*( ABS( A( K,
  516:      $         K ) )+ABS( A( K-1, K-1 ) ) ) ) ) THEN
  517:                A( K, K-1 ) = CZERO
  518:                ISTART2 = K
  519:                EXIT
  520:             END IF
  521:          END DO
  522: 
  523: *        Get range to apply rotations to
  524:          IF ( ILSCHUR ) THEN
  525:             ISTARTM = 1
  526:             ISTOPM = N
  527:          ELSE
  528:             ISTARTM = ISTART2
  529:             ISTOPM = ISTOP
  530:          END IF
  531: 
  532: *        Check infinite eigenvalues, this is done without blocking so might
  533: *        slow down the method when many infinite eigenvalues are present
  534:          K = ISTOP
  535:          DO WHILE ( K.GE.ISTART2 )
  536: 
  537:             IF( ABS( B( K, K ) ) .LT. BTOL ) THEN
  538: *              A diagonal element of B is negligable, move it
  539: *              to the top and deflate it
  540:                
  541:                DO K2 = K, ISTART2+1, -1
  542:                   CALL ZLARTG( B( K2-1, K2 ), B( K2-1, K2-1 ), C1, S1,
  543:      $                         TEMP )
  544:                   B( K2-1, K2 ) = TEMP
  545:                   B( K2-1, K2-1 ) = CZERO
  546: 
  547:                   CALL ZROT( K2-2-ISTARTM+1, B( ISTARTM, K2 ), 1,
  548:      $                       B( ISTARTM, K2-1 ), 1, C1, S1 )
  549:                   CALL ZROT( MIN( K2+1, ISTOP )-ISTARTM+1, A( ISTARTM,
  550:      $                       K2 ), 1, A( ISTARTM, K2-1 ), 1, C1, S1 )
  551:                   IF ( ILZ ) THEN
  552:                      CALL ZROT( N, Z( 1, K2 ), 1, Z( 1, K2-1 ), 1, C1,
  553:      $                          S1 )
  554:                   END IF
  555: 
  556:                   IF( K2.LT.ISTOP ) THEN
  557:                      CALL ZLARTG( A( K2, K2-1 ), A( K2+1, K2-1 ), C1,
  558:      $                            S1, TEMP )
  559:                      A( K2, K2-1 ) = TEMP
  560:                      A( K2+1, K2-1 ) = CZERO
  561: 
  562:                      CALL ZROT( ISTOPM-K2+1, A( K2, K2 ), LDA, A( K2+1,
  563:      $                          K2 ), LDA, C1, S1 )
  564:                      CALL ZROT( ISTOPM-K2+1, B( K2, K2 ), LDB, B( K2+1,
  565:      $                          K2 ), LDB, C1, S1 )
  566:                      IF( ILQ ) THEN
  567:                         CALL ZROT( N, Q( 1, K2 ), 1, Q( 1, K2+1 ), 1,
  568:      $                             C1, DCONJG( S1 ) )
  569:                      END IF
  570:                   END IF
  571: 
  572:                END DO
  573: 
  574:                IF( ISTART2.LT.ISTOP )THEN
  575:                   CALL ZLARTG( A( ISTART2, ISTART2 ), A( ISTART2+1,
  576:      $                         ISTART2 ), C1, S1, TEMP )
  577:                   A( ISTART2, ISTART2 ) = TEMP
  578:                   A( ISTART2+1, ISTART2 ) = CZERO
  579: 
  580:                   CALL ZROT( ISTOPM-( ISTART2+1 )+1, A( ISTART2,
  581:      $                       ISTART2+1 ), LDA, A( ISTART2+1,
  582:      $                       ISTART2+1 ), LDA, C1, S1 )
  583:                   CALL ZROT( ISTOPM-( ISTART2+1 )+1, B( ISTART2,
  584:      $                       ISTART2+1 ), LDB, B( ISTART2+1,
  585:      $                       ISTART2+1 ), LDB, C1, S1 )
  586:                   IF( ILQ ) THEN
  587:                      CALL ZROT( N, Q( 1, ISTART2 ), 1, Q( 1,
  588:      $                          ISTART2+1 ), 1, C1, DCONJG( S1 ) )
  589:                   END IF
  590:                END IF
  591: 
  592:                ISTART2 = ISTART2+1
  593:    
  594:             END IF
  595:             K = K-1
  596:          END DO
  597: 
  598: *        istart2 now points to the top of the bottom right
  599: *        unreduced Hessenberg block
  600:          IF ( ISTART2 .GE. ISTOP ) THEN
  601:             ISTOP = ISTART2-1
  602:             LD = 0
  603:             ESHIFT = CZERO
  604:             CYCLE
  605:          END IF
  606: 
  607:          NW = NWR
  608:          NSHIFTS = NSR
  609:          NBLOCK = NBR
  610: 
  611:          IF ( ISTOP-ISTART2+1 .LT. NMIN ) THEN
  612: *           Setting nw to the size of the subblock will make AED deflate
  613: *           all the eigenvalues. This is slightly more efficient than just
  614: *           using qz_small because the off diagonal part gets updated via BLAS.
  615:             IF ( ISTOP-ISTART+1 .LT. NMIN ) THEN
  616:                NW = ISTOP-ISTART+1
  617:                ISTART2 = ISTART
  618:             ELSE
  619:                NW = ISTOP-ISTART2+1
  620:             END IF
  621:          END IF
  622: 
  623: *
  624: *        Time for AED
  625: *
  626:          CALL ZLAQZ2( ILSCHUR, ILQ, ILZ, N, ISTART2, ISTOP, NW, A, LDA,
  627:      $                B, LDB, Q, LDQ, Z, LDZ, N_UNDEFLATED, N_DEFLATED,
  628:      $                ALPHA, BETA, WORK, NW, WORK( NW**2+1 ), NW,
  629:      $                WORK( 2*NW**2+1 ), LWORK-2*NW**2, RWORK, REC,
  630:      $                AED_INFO )
  631: 
  632:          IF ( N_DEFLATED > 0 ) THEN
  633:             ISTOP = ISTOP-N_DEFLATED
  634:             LD = 0
  635:             ESHIFT = CZERO
  636:          END IF
  637: 
  638:          IF ( 100*N_DEFLATED > NIBBLE*( N_DEFLATED+N_UNDEFLATED ) .OR.
  639:      $      ISTOP-ISTART2+1 .LT. NMIN ) THEN
  640: *           AED has uncovered many eigenvalues. Skip a QZ sweep and run
  641: *           AED again.
  642:             CYCLE
  643:          END IF
  644: 
  645:          LD = LD+1
  646: 
  647:          NS = MIN( NSHIFTS, ISTOP-ISTART2 )
  648:          NS = MIN( NS, N_UNDEFLATED )
  649:          SHIFTPOS = ISTOP-N_DEFLATED-N_UNDEFLATED+1
  650: 
  651:          IF ( MOD( LD, 6 ) .EQ. 0 ) THEN
  652:   653: *           Exceptional shift.  Chosen for no particularly good reason.
  654: *
  655:             IF( ( DBLE( MAXIT )*SAFMIN )*ABS( A( ISTOP,
  656:      $         ISTOP-1 ) ).LT.ABS( A( ISTOP-1, ISTOP-1 ) ) ) THEN
  657:                ESHIFT = A( ISTOP, ISTOP-1 )/B( ISTOP-1, ISTOP-1 )
  658:             ELSE
  659:                ESHIFT = ESHIFT+CONE/( SAFMIN*DBLE( MAXIT ) )
  660:             END IF
  661:             ALPHA( SHIFTPOS ) = CONE
  662:             BETA( SHIFTPOS ) = ESHIFT
  663:             NS = 1
  664:          END IF
  665: 
  666: *
  667: *        Time for a QZ sweep
  668: *
  669:          CALL ZLAQZ3( ILSCHUR, ILQ, ILZ, N, ISTART2, ISTOP, NS, NBLOCK,
  670:      $                ALPHA( SHIFTPOS ), BETA( SHIFTPOS ), A, LDA, B,
  671:      $                LDB, Q, LDQ, Z, LDZ, WORK, NBLOCK, WORK( NBLOCK**
  672:      $                2+1 ), NBLOCK, WORK( 2*NBLOCK**2+1 ),
  673:      $                LWORK-2*NBLOCK**2, SWEEP_INFO )
  674: 
  675:       END DO
  676: 
  677: *
  678: *     Call ZHGEQZ to normalize the eigenvalue blocks and set the eigenvalues
  679: *     If all the eigenvalues have been found, ZHGEQZ will not do any iterations
  680: *     and only normalize the blocks. In case of a rare convergence failure,
  681: *     the single shift might perform better.
  682: *
  683:    80 CALL ZHGEQZ( WANTS, WANTQ, WANTZ, N, ILO, IHI, A, LDA, B, LDB,
  684:      $             ALPHA, BETA, Q, LDQ, Z, LDZ, WORK, LWORK, RWORK,
  685:      $             NORM_INFO )
  686:       
  687:       INFO = NORM_INFO
  688: 
  689:       END SUBROUTINE

CVSweb interface <joel.bertrand@systella.fr>