LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zgeqrt2.f
Go to the documentation of this file.
1*> \brief \b ZGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY representation of Q.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZGEQRT2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgeqrt2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgeqrt2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgeqrt2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE ZGEQRT2( M, N, A, LDA, T, LDT, INFO )
22*
23* .. Scalar Arguments ..
24* INTEGER INFO, LDA, LDT, M, N
25* ..
26* .. Array Arguments ..
27* COMPLEX*16 A( LDA, * ), T( LDT, * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZGEQRT2 computes a QR factorization of a complex M-by-N matrix A,
37*> using the compact WY representation of Q.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] M
44*> \verbatim
45*> M is INTEGER
46*> The number of rows of the matrix A. M >= N.
47*> \endverbatim
48*>
49*> \param[in] N
50*> \verbatim
51*> N is INTEGER
52*> The number of columns of the matrix A. N >= 0.
53*> \endverbatim
54*>
55*> \param[in,out] A
56*> \verbatim
57*> A is COMPLEX*16 array, dimension (LDA,N)
58*> On entry, the complex M-by-N matrix A. On exit, the elements on and
59*> above the diagonal contain the N-by-N upper triangular matrix R; the
60*> elements below the diagonal are the columns of V. See below for
61*> further details.
62*> \endverbatim
63*>
64*> \param[in] LDA
65*> \verbatim
66*> LDA is INTEGER
67*> The leading dimension of the array A. LDA >= max(1,M).
68*> \endverbatim
69*>
70*> \param[out] T
71*> \verbatim
72*> T is COMPLEX*16 array, dimension (LDT,N)
73*> The N-by-N upper triangular factor of the block reflector.
74*> The elements on and above the diagonal contain the block
75*> reflector T; the elements below the diagonal are not used.
76*> See below for further details.
77*> \endverbatim
78*>
79*> \param[in] LDT
80*> \verbatim
81*> LDT is INTEGER
82*> The leading dimension of the array T. LDT >= max(1,N).
83*> \endverbatim
84*>
85*> \param[out] INFO
86*> \verbatim
87*> INFO is INTEGER
88*> = 0: successful exit
89*> < 0: if INFO = -i, the i-th argument had an illegal value
90*> \endverbatim
91*
92* Authors:
93* ========
94*
95*> \author Univ. of Tennessee
96*> \author Univ. of California Berkeley
97*> \author Univ. of Colorado Denver
98*> \author NAG Ltd.
99*
100*> \ingroup geqrt2
101*
102*> \par Further Details:
103* =====================
104*>
105*> \verbatim
106*>
107*> The matrix V stores the elementary reflectors H(i) in the i-th column
108*> below the diagonal. For example, if M=5 and N=3, the matrix V is
109*>
110*> V = ( 1 )
111*> ( v1 1 )
112*> ( v1 v2 1 )
113*> ( v1 v2 v3 )
114*> ( v1 v2 v3 )
115*>
116*> where the vi's represent the vectors which define H(i), which are returned
117*> in the matrix A. The 1's along the diagonal of V are not stored in A. The
118*> block reflector H is then given by
119*>
120*> H = I - V * T * V**H
121*>
122*> where V**H is the conjugate transpose of V.
123*> \endverbatim
124*>
125* =====================================================================
126 SUBROUTINE zgeqrt2( M, N, A, LDA, T, LDT, INFO )
127*
128* -- LAPACK computational routine --
129* -- LAPACK is a software package provided by Univ. of Tennessee, --
130* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131*
132* .. Scalar Arguments ..
133 INTEGER INFO, LDA, LDT, M, N
134* ..
135* .. Array Arguments ..
136 COMPLEX*16 A( LDA, * ), T( LDT, * )
137* ..
138*
139* =====================================================================
140*
141* .. Parameters ..
142 COMPLEX*16 ONE, ZERO
143 parameter( one = (1.0d+00,0.0d+00), zero = (0.0d+00,0.0d+00) )
144* ..
145* .. Local Scalars ..
146 INTEGER I, K
147 COMPLEX*16 AII, ALPHA
148* ..
149* .. External Subroutines ..
150 EXTERNAL zlarfg, zgemv, zgerc, ztrmv, xerbla
151* ..
152* .. Executable Statements ..
153*
154* Test the input arguments
155*
156 info = 0
157 IF( n.LT.0 ) THEN
158 info = -2
159 ELSE IF( m.LT.n ) THEN
160 info = -1
161 ELSE IF( lda.LT.max( 1, m ) ) THEN
162 info = -4
163 ELSE IF( ldt.LT.max( 1, n ) ) THEN
164 info = -6
165 END IF
166 IF( info.NE.0 ) THEN
167 CALL xerbla( 'ZGEQRT2', -info )
168 RETURN
169 END IF
170*
171 k = min( m, n )
172*
173 DO i = 1, k
174*
175* Generate elem. refl. H(i) to annihilate A(i+1:m,i), tau(I) -> T(I,1)
176*
177 CALL zlarfg( m-i+1, a( i, i ), a( min( i+1, m ), i ), 1,
178 $ t( i, 1 ) )
179 IF( i.LT.n ) THEN
180*
181* Apply H(i) to A(I:M,I+1:N) from the left
182*
183 aii = a( i, i )
184 a( i, i ) = one
185*
186* W(1:N-I) := A(I:M,I+1:N)^H * A(I:M,I) [W = T(:,N)]
187*
188 CALL zgemv( 'C',m-i+1, n-i, one, a( i, i+1 ), lda,
189 $ a( i, i ), 1, zero, t( 1, n ), 1 )
190*
191* A(I:M,I+1:N) = A(I:m,I+1:N) + alpha*A(I:M,I)*W(1:N-1)^H
192*
193 alpha = -conjg(t( i, 1 ))
194 CALL zgerc( m-i+1, n-i, alpha, a( i, i ), 1,
195 $ t( 1, n ), 1, a( i, i+1 ), lda )
196 a( i, i ) = aii
197 END IF
198 END DO
199*
200 DO i = 2, n
201 aii = a( i, i )
202 a( i, i ) = one
203*
204* T(1:I-1,I) := alpha * A(I:M,1:I-1)**H * A(I:M,I)
205*
206 alpha = -t( i, 1 )
207 CALL zgemv( 'C', m-i+1, i-1, alpha, a( i, 1 ), lda,
208 $ a( i, i ), 1, zero, t( 1, i ), 1 )
209 a( i, i ) = aii
210*
211* T(1:I-1,I) := T(1:I-1,1:I-1) * T(1:I-1,I)
212*
213 CALL ztrmv( 'U', 'N', 'N', i-1, t, ldt, t( 1, i ), 1 )
214*
215* T(I,I) = tau(I)
216*
217 t( i, i ) = t( i, 1 )
218 t( i, 1) = zero
219 END DO
220
221*
222* End of ZGEQRT2
223*
224 END
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 zgeqrt2(m, n, a, lda, t, ldt, info)
ZGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY represen...
Definition zgeqrt2.f:127
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:106
subroutine ztrmv(uplo, trans, diag, n, a, lda, x, incx)
ZTRMV
Definition ztrmv.f:147