LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zgeqrt2()

subroutine zgeqrt2 ( integer m,
integer n,
complex*16, dimension( lda, * ) a,
integer lda,
complex*16, dimension( ldt, * ) t,
integer ldt,
integer info )

ZGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY representation of Q.

Download ZGEQRT2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZGEQRT2 computes a QR factorization of a complex M-by-N matrix A,
!> using the compact WY representation of Q.
!> 
Parameters
[in]M
!>          M is INTEGER
!>          The number of rows of the matrix A.  M >= N.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of the matrix A.  N >= 0.
!> 
[in,out]A
!>          A is COMPLEX*16 array, dimension (LDA,N)
!>          On entry, the complex M-by-N matrix A.  On exit, the elements on and
!>          above the diagonal contain the N-by-N upper triangular matrix R; the
!>          elements below the diagonal are the columns of V.  See below for
!>          further details.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,M).
!> 
[out]T
!>          T is COMPLEX*16 array, dimension (LDT,N)
!>          The N-by-N upper triangular factor of the block reflector.
!>          The elements on and above the diagonal contain the block
!>          reflector T; the elements below the diagonal are not used.
!>          See below for further details.
!> 
[in]LDT
!>          LDT is INTEGER
!>          The leading dimension of the array T.  LDT >= max(1,N).
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>  The matrix V stores the elementary reflectors H(i) in the i-th column
!>  below the diagonal. For example, if M=5 and N=3, the matrix V is
!>
!>               V = (  1       )
!>                   ( v1  1    )
!>                   ( v1 v2  1 )
!>                   ( v1 v2 v3 )
!>                   ( v1 v2 v3 )
!>
!>  where the vi's represent the vectors which define H(i), which are returned
!>  in the matrix A.  The 1's along the diagonal of V are not stored in A.  The
!>  block reflector H is then given by
!>
!>               H = I - V * T * V**H
!>
!>  where V**H is the conjugate transpose of V.
!> 

Definition at line 124 of file zgeqrt2.f.

125*
126* -- LAPACK computational routine --
127* -- LAPACK is a software package provided by Univ. of Tennessee, --
128* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129*
130* .. Scalar Arguments ..
131 INTEGER INFO, LDA, LDT, M, N
132* ..
133* .. Array Arguments ..
134 COMPLEX*16 A( LDA, * ), T( LDT, * )
135* ..
136*
137* =====================================================================
138*
139* .. Parameters ..
140 COMPLEX*16 ONE, ZERO
141 parameter( one = (1.0d+00,0.0d+00), zero = (0.0d+00,0.0d+00) )
142* ..
143* .. Local Scalars ..
144 INTEGER I, K
145 COMPLEX*16 AII, ALPHA
146* ..
147* .. External Subroutines ..
148 EXTERNAL zlarfg, zgemv, zgerc, ztrmv, xerbla
149* ..
150* .. Executable Statements ..
151*
152* Test the input arguments
153*
154 info = 0
155 IF( n.LT.0 ) THEN
156 info = -2
157 ELSE IF( m.LT.n ) THEN
158 info = -1
159 ELSE IF( lda.LT.max( 1, m ) ) THEN
160 info = -4
161 ELSE IF( ldt.LT.max( 1, n ) ) THEN
162 info = -6
163 END IF
164 IF( info.NE.0 ) THEN
165 CALL xerbla( 'ZGEQRT2', -info )
166 RETURN
167 END IF
168*
169 k = min( m, n )
170*
171 DO i = 1, k
172*
173* Generate elem. refl. H(i) to annihilate A(i+1:m,i), tau(I) -> T(I,1)
174*
175 CALL zlarfg( m-i+1, a( i, i ), a( min( i+1, m ), i ), 1,
176 $ t( i, 1 ) )
177 IF( i.LT.n ) THEN
178*
179* Apply H(i) to A(I:M,I+1:N) from the left
180*
181 aii = a( i, i )
182 a( i, i ) = one
183*
184* W(1:N-I) := A(I:M,I+1:N)^H * A(I:M,I) [W = T(:,N)]
185*
186 CALL zgemv( 'C',m-i+1, n-i, one, a( i, i+1 ), lda,
187 $ a( i, i ), 1, zero, t( 1, n ), 1 )
188*
189* A(I:M,I+1:N) = A(I:m,I+1:N) + alpha*A(I:M,I)*W(1:N-1)^H
190*
191 alpha = -conjg(t( i, 1 ))
192 CALL zgerc( m-i+1, n-i, alpha, a( i, i ), 1,
193 $ t( 1, n ), 1, a( i, i+1 ), lda )
194 a( i, i ) = aii
195 END IF
196 END DO
197*
198 DO i = 2, n
199 aii = a( i, i )
200 a( i, i ) = one
201*
202* T(1:I-1,I) := alpha * A(I:M,1:I-1)**H * A(I:M,I)
203*
204 alpha = -t( i, 1 )
205 CALL zgemv( 'C', m-i+1, i-1, alpha, a( i, 1 ), lda,
206 $ a( i, i ), 1, zero, t( 1, i ), 1 )
207 a( i, i ) = aii
208*
209* T(1:I-1,I) := T(1:I-1,1:I-1) * T(1:I-1,I)
210*
211 CALL ztrmv( 'U', 'N', 'N', i-1, t, ldt, t( 1, i ), 1 )
212*
213* T(I,I) = tau(I)
214*
215 t( i, i ) = t( i, 1 )
216 t( i, 1) = zero
217 END DO
218
219*
220* End of ZGEQRT2
221*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:160
subroutine zgerc(m, n, alpha, x, incx, y, incy, a, lda)
ZGERC
Definition zgerc.f:130
subroutine zlarfg(n, alpha, x, incx, tau)
ZLARFG generates an elementary reflector (Householder matrix).
Definition zlarfg.f:104
subroutine ztrmv(uplo, trans, diag, n, a, lda, x, incx)
ZTRMV
Definition ztrmv.f:147
Here is the call graph for this function:
Here is the caller graph for this function: