LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dgeqrt2.f
Go to the documentation of this file.
1*> \brief \b DGEQRT2 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*> Download DGEQRT2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgeqrt2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgeqrt2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgeqrt2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DGEQRT2( M, N, A, LDA, T, LDT, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDA, LDT, M, N
23* ..
24* .. Array Arguments ..
25* DOUBLE PRECISION A( LDA, * ), T( LDT, * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> DGEQRT2 computes a QR factorization of a real M-by-N matrix A,
35*> using the compact WY representation of Q.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] M
42*> \verbatim
43*> M is INTEGER
44*> The number of rows of the matrix A. M >= N.
45*> \endverbatim
46*>
47*> \param[in] N
48*> \verbatim
49*> N is INTEGER
50*> The number of columns of the matrix A. N >= 0.
51*> \endverbatim
52*>
53*> \param[in,out] A
54*> \verbatim
55*> A is DOUBLE PRECISION array, dimension (LDA,N)
56*> On entry, the real M-by-N matrix A. On exit, the elements on and
57*> above the diagonal contain the N-by-N upper triangular matrix R; the
58*> elements below the diagonal are the columns of V. See below for
59*> further details.
60*> \endverbatim
61*>
62*> \param[in] LDA
63*> \verbatim
64*> LDA is INTEGER
65*> The leading dimension of the array A. LDA >= max(1,M).
66*> \endverbatim
67*>
68*> \param[out] T
69*> \verbatim
70*> T is DOUBLE PRECISION array, dimension (LDT,N)
71*> The N-by-N upper triangular factor of the block reflector.
72*> The elements on and above the diagonal contain the block
73*> reflector T; the elements below the diagonal are not used.
74*> See below for further details.
75*> \endverbatim
76*>
77*> \param[in] LDT
78*> \verbatim
79*> LDT is INTEGER
80*> The leading dimension of the array T. LDT >= max(1,N).
81*> \endverbatim
82*>
83*> \param[out] INFO
84*> \verbatim
85*> INFO is INTEGER
86*> = 0: successful exit
87*> < 0: if INFO = -i, the i-th argument had an illegal value
88*> \endverbatim
89*
90* Authors:
91* ========
92*
93*> \author Univ. of Tennessee
94*> \author Univ. of California Berkeley
95*> \author Univ. of Colorado Denver
96*> \author NAG Ltd.
97*
98*> \ingroup geqrt2
99*
100*> \par Further Details:
101* =====================
102*>
103*> \verbatim
104*>
105*> The matrix V stores the elementary reflectors H(i) in the i-th column
106*> below the diagonal. For example, if M=5 and N=3, the matrix V is
107*>
108*> V = ( 1 )
109*> ( v1 1 )
110*> ( v1 v2 1 )
111*> ( v1 v2 v3 )
112*> ( v1 v2 v3 )
113*>
114*> where the vi's represent the vectors which define H(i), which are returned
115*> in the matrix A. The 1's along the diagonal of V are not stored in A. The
116*> block reflector H is then given by
117*>
118*> H = I - V * T * V**T
119*>
120*> where V**T is the transpose of V.
121*> \endverbatim
122*>
123* =====================================================================
124 SUBROUTINE dgeqrt2( M, N, A, LDA, T, LDT, INFO )
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 DOUBLE PRECISION A( LDA, * ), T( LDT, * )
135* ..
136*
137* =====================================================================
138*
139* .. Parameters ..
140 DOUBLE PRECISION ONE, ZERO
141 parameter( one = 1.0d+00, zero = 0.0d+00 )
142* ..
143* .. Local Scalars ..
144 INTEGER I, K
145 DOUBLE PRECISION AII, ALPHA
146* ..
147* .. External Subroutines ..
148 EXTERNAL dlarfg, dgemv, dger, dtrmv, 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( 'DGEQRT2', -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 dlarfg( 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 dgemv( 'T',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 = -(t( i, 1 ))
192 CALL dger( 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)**T * A(I:M,I)
203*
204 alpha = -t( i, 1 )
205 CALL dgemv( 'T', 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 dtrmv( '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 DGEQRT2
221*
222 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158
subroutine dgeqrt2(m, n, a, lda, t, ldt, info)
DGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY represen...
Definition dgeqrt2.f:125
subroutine dger(m, n, alpha, x, incx, y, incy, a, lda)
DGER
Definition dger.f:130
subroutine dlarfg(n, alpha, x, incx, tau)
DLARFG generates an elementary reflector (Householder matrix).
Definition dlarfg.f:104
subroutine dtrmv(uplo, trans, diag, n, a, lda, x, incx)
DTRMV
Definition dtrmv.f:147