📄 zgbbrd.f
字号:
SUBROUTINE ZGBBRD( VECT, M, N, NCC, KL, KU, AB, LDAB, D, E, Q,
$ LDQ, PT, LDPT, C, LDC, WORK, RWORK, INFO )
*
* -- LAPACK routine (version 3.1) --
* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
* November 2006
*
* .. Scalar Arguments ..
CHARACTER VECT
INTEGER INFO, KL, KU, LDAB, LDC, LDPT, LDQ, M, N, NCC
* ..
* .. Array Arguments ..
DOUBLE PRECISION D( * ), E( * ), RWORK( * )
COMPLEX*16 AB( LDAB, * ), C( LDC, * ), PT( LDPT, * ),
$ Q( LDQ, * ), WORK( * )
* ..
*
* Purpose
* =======
*
* ZGBBRD reduces a complex general m-by-n band matrix A to real upper
* bidiagonal form B by a unitary transformation: Q' * A * P = B.
*
* The routine computes B, and optionally forms Q or P', or computes
* Q'*C for a given matrix C.
*
* Arguments
* =========
*
* VECT (input) CHARACTER*1
* Specifies whether or not the matrices Q and P' are to be
* formed.
* = 'N': do not form Q or P';
* = 'Q': form Q only;
* = 'P': form P' only;
* = 'B': form both.
*
* M (input) INTEGER
* The number of rows of the matrix A. M >= 0.
*
* N (input) INTEGER
* The number of columns of the matrix A. N >= 0.
*
* NCC (input) INTEGER
* The number of columns of the matrix C. NCC >= 0.
*
* KL (input) INTEGER
* The number of subdiagonals of the matrix A. KL >= 0.
*
* KU (input) INTEGER
* The number of superdiagonals of the matrix A. KU >= 0.
*
* AB (input/output) COMPLEX*16 array, dimension (LDAB,N)
* On entry, the m-by-n band matrix A, stored in rows 1 to
* KL+KU+1. The j-th column of A is stored in the j-th column of
* the array AB as follows:
* AB(ku+1+i-j,j) = A(i,j) for max(1,j-ku)<=i<=min(m,j+kl).
* On exit, A is overwritten by values generated during the
* reduction.
*
* LDAB (input) INTEGER
* The leading dimension of the array A. LDAB >= KL+KU+1.
*
* D (output) DOUBLE PRECISION array, dimension (min(M,N))
* The diagonal elements of the bidiagonal matrix B.
*
* E (output) DOUBLE PRECISION array, dimension (min(M,N)-1)
* The superdiagonal elements of the bidiagonal matrix B.
*
* Q (output) COMPLEX*16 array, dimension (LDQ,M)
* If VECT = 'Q' or 'B', the m-by-m unitary matrix Q.
* If VECT = 'N' or 'P', the array Q is not referenced.
*
* LDQ (input) INTEGER
* The leading dimension of the array Q.
* LDQ >= max(1,M) if VECT = 'Q' or 'B'; LDQ >= 1 otherwise.
*
* PT (output) COMPLEX*16 array, dimension (LDPT,N)
* If VECT = 'P' or 'B', the n-by-n unitary matrix P'.
* If VECT = 'N' or 'Q', the array PT is not referenced.
*
* LDPT (input) INTEGER
* The leading dimension of the array PT.
* LDPT >= max(1,N) if VECT = 'P' or 'B'; LDPT >= 1 otherwise.
*
* C (input/output) COMPLEX*16 array, dimension (LDC,NCC)
* On entry, an m-by-ncc matrix C.
* On exit, C is overwritten by Q'*C.
* C is not referenced if NCC = 0.
*
* LDC (input) INTEGER
* The leading dimension of the array C.
* LDC >= max(1,M) if NCC > 0; LDC >= 1 if NCC = 0.
*
* WORK (workspace) COMPLEX*16 array, dimension (max(M,N))
*
* RWORK (workspace) DOUBLE PRECISION array, dimension (max(M,N))
*
* INFO (output) INTEGER
* = 0: successful exit.
* < 0: if INFO = -i, the i-th argument had an illegal value.
*
* =====================================================================
*
* .. Parameters ..
DOUBLE PRECISION ZERO
PARAMETER ( ZERO = 0.0D+0 )
COMPLEX*16 CZERO, CONE
PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ),
$ CONE = ( 1.0D+0, 0.0D+0 ) )
* ..
* .. Local Scalars ..
LOGICAL WANTB, WANTC, WANTPT, WANTQ
INTEGER I, INCA, J, J1, J2, KB, KB1, KK, KLM, KLU1,
$ KUN, L, MINMN, ML, ML0, MU, MU0, NR, NRT
DOUBLE PRECISION ABST, RC
COMPLEX*16 RA, RB, RS, T
* ..
* .. External Subroutines ..
EXTERNAL XERBLA, ZLARGV, ZLARTG, ZLARTV, ZLASET, ZROT,
$ ZSCAL
* ..
* .. Intrinsic Functions ..
INTRINSIC ABS, DCONJG, MAX, MIN
* ..
* .. External Functions ..
LOGICAL LSAME
EXTERNAL LSAME
* ..
* .. Executable Statements ..
*
* Test the input parameters
*
WANTB = LSAME( VECT, 'B' )
WANTQ = LSAME( VECT, 'Q' ) .OR. WANTB
WANTPT = LSAME( VECT, 'P' ) .OR. WANTB
WANTC = NCC.GT.0
KLU1 = KL + KU + 1
INFO = 0
IF( .NOT.WANTQ .AND. .NOT.WANTPT .AND. .NOT.LSAME( VECT, 'N' ) )
$ THEN
INFO = -1
ELSE IF( M.LT.0 ) THEN
INFO = -2
ELSE IF( N.LT.0 ) THEN
INFO = -3
ELSE IF( NCC.LT.0 ) THEN
INFO = -4
ELSE IF( KL.LT.0 ) THEN
INFO = -5
ELSE IF( KU.LT.0 ) THEN
INFO = -6
ELSE IF( LDAB.LT.KLU1 ) THEN
INFO = -8
ELSE IF( LDQ.LT.1 .OR. WANTQ .AND. LDQ.LT.MAX( 1, M ) ) THEN
INFO = -12
ELSE IF( LDPT.LT.1 .OR. WANTPT .AND. LDPT.LT.MAX( 1, N ) ) THEN
INFO = -14
ELSE IF( LDC.LT.1 .OR. WANTC .AND. LDC.LT.MAX( 1, M ) ) THEN
INFO = -16
END IF
IF( INFO.NE.0 ) THEN
CALL XERBLA( 'ZGBBRD', -INFO )
RETURN
END IF
*
* Initialize Q and P' to the unit matrix, if needed
*
IF( WANTQ )
$ CALL ZLASET( 'Full', M, M, CZERO, CONE, Q, LDQ )
IF( WANTPT )
$ CALL ZLASET( 'Full', N, N, CZERO, CONE, PT, LDPT )
*
* Quick return if possible.
*
IF( M.EQ.0 .OR. N.EQ.0 )
$ RETURN
*
MINMN = MIN( M, N )
*
IF( KL+KU.GT.1 ) THEN
*
* Reduce to upper bidiagonal form if KU > 0; if KU = 0, reduce
* first to lower bidiagonal form and then transform to upper
* bidiagonal
*
IF( KU.GT.0 ) THEN
ML0 = 1
MU0 = 2
ELSE
ML0 = 2
MU0 = 1
END IF
*
* Wherever possible, plane rotations are generated and applied in
* vector operations of length NR over the index set J1:J2:KLU1.
*
* The complex sines of the plane rotations are stored in WORK,
* and the real cosines in RWORK.
*
KLM = MIN( M-1, KL )
KUN = MIN( N-1, KU )
KB = KLM + KUN
KB1 = KB + 1
INCA = KB1*LDAB
NR = 0
J1 = KLM + 2
J2 = 1 - KUN
*
DO 90 I = 1, MINMN
*
* Reduce i-th column and i-th row of matrix to bidiagonal form
*
ML = KLM + 1
MU = KUN + 1
DO 80 KK = 1, KB
J1 = J1 + KB
J2 = J2 + KB
*
* generate plane rotations to annihilate nonzero elements
* which have been created below the band
*
IF( NR.GT.0 )
$ CALL ZLARGV( NR, AB( KLU1, J1-KLM-1 ), INCA,
$ WORK( J1 ), KB1, RWORK( J1 ), KB1 )
*
* apply plane rotations from the left
*
DO 10 L = 1, KB
IF( J2-KLM+L-1.GT.N ) THEN
NRT = NR - 1
ELSE
NRT = NR
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -