📄 claqr5.f
字号:
SUBROUTINE CLAQR5( WANTT, WANTZ, KACC22, N, KTOP, KBOT, NSHFTS, S,
$ H, LDH, ILOZ, IHIZ, Z, LDZ, V, LDV, U, LDU, NV,
$ WV, LDWV, NH, WH, LDWH )
*
* -- LAPACK auxiliary routine (version 3.1) --
* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
* November 2006
*
* .. Scalar Arguments ..
INTEGER IHIZ, ILOZ, KACC22, KBOT, KTOP, LDH, LDU, LDV,
$ LDWH, LDWV, LDZ, N, NH, NSHFTS, NV
LOGICAL WANTT, WANTZ
* ..
* .. Array Arguments ..
COMPLEX H( LDH, * ), S( * ), U( LDU, * ), V( LDV, * ),
$ WH( LDWH, * ), WV( LDWV, * ), Z( LDZ, * )
* ..
*
* This auxiliary subroutine called by CLAQR0 performs a
* single small-bulge multi-shift QR sweep.
*
* WANTT (input) logical scalar
* WANTT = .true. if the triangular Schur factor
* is being computed. WANTT is set to .false. otherwise.
*
* WANTZ (input) logical scalar
* WANTZ = .true. if the unitary Schur factor is being
* computed. WANTZ is set to .false. otherwise.
*
* KACC22 (input) integer with value 0, 1, or 2.
* Specifies the computation mode of far-from-diagonal
* orthogonal updates.
* = 0: CLAQR5 does not accumulate reflections and does not
* use matrix-matrix multiply to update far-from-diagonal
* matrix entries.
* = 1: CLAQR5 accumulates reflections and uses matrix-matrix
* multiply to update the far-from-diagonal matrix entries.
* = 2: CLAQR5 accumulates reflections, uses matrix-matrix
* multiply to update the far-from-diagonal matrix entries,
* and takes advantage of 2-by-2 block structure during
* matrix multiplies.
*
* N (input) integer scalar
* N is the order of the Hessenberg matrix H upon which this
* subroutine operates.
*
* KTOP (input) integer scalar
* KBOT (input) integer scalar
* These are the first and last rows and columns of an
* isolated diagonal block upon which the QR sweep is to be
* applied. It is assumed without a check that
* either KTOP = 1 or H(KTOP,KTOP-1) = 0
* and
* either KBOT = N or H(KBOT+1,KBOT) = 0.
*
* NSHFTS (input) integer scalar
* NSHFTS gives the number of simultaneous shifts. NSHFTS
* must be positive and even.
*
* S (input) COMPLEX array of size (NSHFTS)
* S contains the shifts of origin that define the multi-
* shift QR sweep.
*
* H (input/output) COMPLEX array of size (LDH,N)
* On input H contains a Hessenberg matrix. On output a
* multi-shift QR sweep with shifts SR(J)+i*SI(J) is applied
* to the isolated diagonal block in rows and columns KTOP
* through KBOT.
*
* LDH (input) integer scalar
* LDH is the leading dimension of H just as declared in the
* calling procedure. LDH.GE.MAX(1,N).
*
* ILOZ (input) INTEGER
* IHIZ (input) INTEGER
* Specify the rows of Z to which transformations must be
* applied if WANTZ is .TRUE.. 1 .LE. ILOZ .LE. IHIZ .LE. N
*
* Z (input/output) COMPLEX array of size (LDZ,IHI)
* If WANTZ = .TRUE., then the QR Sweep unitary
* similarity transformation is accumulated into
* Z(ILOZ:IHIZ,ILO:IHI) from the right.
* If WANTZ = .FALSE., then Z is unreferenced.
*
* LDZ (input) integer scalar
* LDA is the leading dimension of Z just as declared in
* the calling procedure. LDZ.GE.N.
*
* V (workspace) COMPLEX array of size (LDV,NSHFTS/2)
*
* LDV (input) integer scalar
* LDV is the leading dimension of V as declared in the
* calling procedure. LDV.GE.3.
*
* U (workspace) COMPLEX array of size
* (LDU,3*NSHFTS-3)
*
* LDU (input) integer scalar
* LDU is the leading dimension of U just as declared in the
* in the calling subroutine. LDU.GE.3*NSHFTS-3.
*
* NH (input) integer scalar
* NH is the number of columns in array WH available for
* workspace. NH.GE.1.
*
* WH (workspace) COMPLEX array of size (LDWH,NH)
*
* LDWH (input) integer scalar
* Leading dimension of WH just as declared in the
* calling procedure. LDWH.GE.3*NSHFTS-3.
*
* NV (input) integer scalar
* NV is the number of rows in WV agailable for workspace.
* NV.GE.1.
*
* WV (workspace) COMPLEX array of size
* (LDWV,3*NSHFTS-3)
*
* LDWV (input) integer scalar
* LDWV is the leading dimension of WV as declared in the
* in the calling subroutine. LDWV.GE.NV.
*
*
* ================================================================
* Based on contributions by
* Karen Braman and Ralph Byers, Department of Mathematics,
* University of Kansas, USA
*
* ============================================================
* Reference:
*
* K. Braman, R. Byers and R. Mathias, The Multi-Shift QR
* Algorithm Part I: Maintaining Well Focused Shifts, and
* Level 3 Performance, SIAM Journal of Matrix Analysis,
* volume 23, pages 929--947, 2002.
*
* ============================================================
* .. Parameters ..
COMPLEX ZERO, ONE
PARAMETER ( ZERO = ( 0.0e0, 0.0e0 ),
$ ONE = ( 1.0e0, 0.0e0 ) )
REAL RZERO, RONE
PARAMETER ( RZERO = 0.0e0, RONE = 1.0e0 )
* ..
* .. Local Scalars ..
COMPLEX ALPHA, BETA, CDUM, REFSUM
REAL H11, H12, H21, H22, SAFMAX, SAFMIN, SCL,
$ SMLNUM, TST1, TST2, ULP
INTEGER I2, I4, INCOL, J, J2, J4, JBOT, JCOL, JLEN,
$ JROW, JTOP, K, K1, KDU, KMS, KNZ, KRCOL, KZS,
$ M, M22, MBOT, MEND, MSTART, MTOP, NBMPS, NDCOL,
$ NS, NU
LOGICAL ACCUM, BLK22, BMP22
* ..
* .. External Functions ..
REAL SLAMCH
EXTERNAL SLAMCH
* ..
* .. Intrinsic Functions ..
*
INTRINSIC ABS, AIMAG, CONJG, MAX, MIN, MOD, REAL
* ..
* .. Local Arrays ..
COMPLEX VT( 3 )
* ..
* .. External Subroutines ..
EXTERNAL CGEMM, CLACPY, CLAQR1, CLARFG, CLASET, CTRMM,
$ SLABAD
* ..
* .. Statement Functions ..
REAL CABS1
* ..
* .. Statement Function definitions ..
CABS1( CDUM ) = ABS( REAL( CDUM ) ) + ABS( AIMAG( CDUM ) )
* ..
* .. Executable Statements ..
*
* ==== If there are no shifts, then there is nothing to do. ====
*
IF( NSHFTS.LT.2 )
$ RETURN
*
* ==== If the active block is empty or 1-by-1, then there
* . is nothing to do. ====
*
IF( KTOP.GE.KBOT )
$ RETURN
*
* ==== NSHFTS is supposed to be even, but if is odd,
* . then simply reduce it by one. ====
*
NS = NSHFTS - MOD( NSHFTS, 2 )
*
* ==== Machine constants for deflation ====
*
SAFMIN = SLAMCH( 'SAFE MINIMUM' )
SAFMAX = RONE / SAFMIN
CALL SLABAD( SAFMIN, SAFMAX )
ULP = SLAMCH( 'PRECISION' )
SMLNUM = SAFMIN*( REAL( N ) / ULP )
*
* ==== Use accumulated reflections to update far-from-diagonal
* . entries ? ====
*
ACCUM = ( KACC22.EQ.1 ) .OR. ( KACC22.EQ.2 )
*
* ==== If so, exploit the 2-by-2 block structure? ====
*
BLK22 = ( NS.GT.2 ) .AND. ( KACC22.EQ.2 )
*
* ==== clear trash ====
*
IF( KTOP+2.LE.KBOT )
$ H( KTOP+2, KTOP ) = ZERO
*
* ==== NBMPS = number of 2-shift bulges in the chain ====
*
NBMPS = NS / 2
*
* ==== KDU = width of slab ====
*
KDU = 6*NBMPS - 3
*
* ==== Create and chase chains of NBMPS bulges ====
*
DO 210 INCOL = 3*( 1-NBMPS ) + KTOP - 1, KBOT - 2, 3*NBMPS - 2
NDCOL = INCOL + KDU
IF( ACCUM )
$ CALL CLASET( 'ALL', KDU, KDU, ZERO, ONE, U, LDU )
*
* ==== Near-the-diagonal bulge chase. The following loop
* . performs the near-the-diagonal part of a small bulge
* . multi-shift QR sweep. Each 6*NBMPS-2 column diagonal
* . chunk extends from column INCOL to column NDCOL
* . (including both column INCOL and column NDCOL). The
* . following loop chases a 3*NBMPS column long chain of
* . NBMPS bulges 3*NBMPS-2 columns to the right. (INCOL
* . may be less than KTOP and and NDCOL may be greater than
* . KBOT indicating phantom columns from which to chase
* . bulges before they are actually introduced or to which
* . to chase bulges beyond column KBOT.) ====
*
DO 140 KRCOL = INCOL, MIN( INCOL+3*NBMPS-3, KBOT-2 )
*
* ==== Bulges number MTOP to MBOT are active double implicit
* . shift bulges. There may or may not also be small
* . 2-by-2 bulge, if there is room. The inactive bulges
* . (if any) must wait until the active bulges have moved
* . down the diagonal to make room. The phantom matrix
* . paradigm described above helps keep track. ====
*
MTOP = MAX( 1, ( ( KTOP-1 )-KRCOL+2 ) / 3+1 )
MBOT = MIN( NBMPS, ( KBOT-KRCOL ) / 3 )
M22 = MBOT + 1
BMP22 = ( MBOT.LT.NBMPS ) .AND. ( KRCOL+3*( M22-1 ) ).EQ.
$ ( KBOT-2 )
*
* ==== Generate reflections to chase the chain right
* . one column. (The minimum value of K is KTOP-1.) ====
*
DO 10 M = MTOP, MBOT
K = KRCOL + 3*( M-1 )
IF( K.EQ.KTOP-1 ) THEN
CALL CLAQR1( 3, H( KTOP, KTOP ), LDH, S( 2*M-1 ),
$ S( 2*M ), V( 1, M ) )
ALPHA = V( 1, M )
CALL CLARFG( 3, ALPHA, V( 2, M ), 1, V( 1, M ) )
ELSE
BETA = H( K+1, K )
V( 2, M ) = H( K+2, K )
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -