LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dtzrqf.f
Go to the documentation of this file.
1*> \brief \b DTZRQF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DTZRQF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtzrqf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtzrqf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtzrqf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DTZRQF( M, N, A, LDA, TAU, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, LDA, M, N
23* ..
24* .. Array Arguments ..
25* DOUBLE PRECISION A( LDA, * ), TAU( * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> This routine is deprecated and has been replaced by routine DTZRZF.
35*>
36*> DTZRQF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A
37*> to upper triangular form by means of orthogonal transformations.
38*>
39*> The upper trapezoidal matrix A is factored as
40*>
41*> A = ( R 0 ) * Z,
42*>
43*> where Z is an N-by-N orthogonal matrix and R is an M-by-M upper
44*> triangular matrix.
45*> \endverbatim
46*
47* Arguments:
48* ==========
49*
50*> \param[in] M
51*> \verbatim
52*> M is INTEGER
53*> The number of rows of the matrix A. M >= 0.
54*> \endverbatim
55*>
56*> \param[in] N
57*> \verbatim
58*> N is INTEGER
59*> The number of columns of the matrix A. N >= M.
60*> \endverbatim
61*>
62*> \param[in,out] A
63*> \verbatim
64*> A is DOUBLE PRECISION array, dimension (LDA,N)
65*> On entry, the leading M-by-N upper trapezoidal part of the
66*> array A must contain the matrix to be factorized.
67*> On exit, the leading M-by-M upper triangular part of A
68*> contains the upper triangular matrix R, and elements M+1 to
69*> N of the first M rows of A, with the array TAU, represent the
70*> orthogonal matrix Z as a product of M elementary reflectors.
71*> \endverbatim
72*>
73*> \param[in] LDA
74*> \verbatim
75*> LDA is INTEGER
76*> The leading dimension of the array A. LDA >= max(1,M).
77*> \endverbatim
78*>
79*> \param[out] TAU
80*> \verbatim
81*> TAU is DOUBLE PRECISION array, dimension (M)
82*> The scalar factors of the elementary reflectors.
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 doubleOTHERcomputational
101*
102*> \par Further Details:
103* =====================
104*>
105*> \verbatim
106*>
107*> The factorization is obtained by Householder's method. The kth
108*> transformation matrix, Z( k ), which is used to introduce zeros into
109*> the ( m - k + 1 )th row of A, is given in the form
110*>
111*> Z( k ) = ( I 0 ),
112*> ( 0 T( k ) )
113*>
114*> where
115*>
116*> T( k ) = I - tau*u( k )*u( k )**T, u( k ) = ( 1 ),
117*> ( 0 )
118*> ( z( k ) )
119*>
120*> tau is a scalar and z( k ) is an ( n - m ) element vector.
121*> tau and z( k ) are chosen to annihilate the elements of the kth row
122*> of X.
123*>
124*> The scalar tau is returned in the kth element of TAU and the vector
125*> u( k ) in the kth row of A, such that the elements of z( k ) are
126*> in a( k, m + 1 ), ..., a( k, n ). The elements of R are returned in
127*> the upper triangular part of A.
128*>
129*> Z is given by
130*>
131*> Z = Z( 1 ) * Z( 2 ) * ... * Z( m ).
132*> \endverbatim
133*>
134* =====================================================================
135 SUBROUTINE dtzrqf( M, N, A, LDA, TAU, INFO )
136*
137* -- LAPACK computational routine --
138* -- LAPACK is a software package provided by Univ. of Tennessee, --
139* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140*
141* .. Scalar Arguments ..
142 INTEGER INFO, LDA, M, N
143* ..
144* .. Array Arguments ..
145 DOUBLE PRECISION A( LDA, * ), TAU( * )
146* ..
147*
148* =====================================================================
149*
150* .. Parameters ..
151 DOUBLE PRECISION ONE, ZERO
152 parameter( one = 1.0d+0, zero = 0.0d+0 )
153* ..
154* .. Local Scalars ..
155 INTEGER I, K, M1
156* ..
157* .. Intrinsic Functions ..
158 INTRINSIC max, min
159* ..
160* .. External Subroutines ..
161 EXTERNAL daxpy, dcopy, dgemv, dger, dlarfg, xerbla
162* ..
163* .. Executable Statements ..
164*
165* Test the input parameters.
166*
167 info = 0
168 IF( m.LT.0 ) THEN
169 info = -1
170 ELSE IF( n.LT.m ) THEN
171 info = -2
172 ELSE IF( lda.LT.max( 1, m ) ) THEN
173 info = -4
174 END IF
175 IF( info.NE.0 ) THEN
176 CALL xerbla( 'DTZRQF', -info )
177 RETURN
178 END IF
179*
180* Perform the factorization.
181*
182 IF( m.EQ.0 )
183 $ RETURN
184 IF( m.EQ.n ) THEN
185 DO 10 i = 1, n
186 tau( i ) = zero
187 10 CONTINUE
188 ELSE
189 m1 = min( m+1, n )
190 DO 20 k = m, 1, -1
191*
192* Use a Householder reflection to zero the kth row of A.
193* First set up the reflection.
194*
195 CALL dlarfg( n-m+1, a( k, k ), a( k, m1 ), lda,
196 $ tau( k ) )
197*
198 IF( ( tau( k ).NE.zero ) .AND. ( k.GT.1 ) ) THEN
199*
200* We now perform the operation A := A*P( k ).
201*
202* Use the first ( k - 1 ) elements of TAU to store a( k ),
203* where a( k ) consists of the first ( k - 1 ) elements of
204* the kth column of A. Also let B denote the first
205* ( k - 1 ) rows of the last ( n - m ) columns of A.
206*
207 CALL dcopy( k-1, a( 1, k ), 1, tau, 1 )
208*
209* Form w = a( k ) + B*z( k ) in TAU.
210*
211 CALL dgemv( 'No transpose', k-1, n-m, one, a( 1, m1 ),
212 $ lda, a( k, m1 ), lda, one, tau, 1 )
213*
214* Now form a( k ) := a( k ) - tau*w
215* and B := B - tau*w*z( k )**T.
216*
217 CALL daxpy( k-1, -tau( k ), tau, 1, a( 1, k ), 1 )
218 CALL dger( k-1, n-m, -tau( k ), tau, 1, a( k, m1 ),
219 $ lda, a( 1, m1 ), lda )
220 END IF
221 20 CONTINUE
222 END IF
223*
224 RETURN
225*
226* End of DTZRQF
227*
228 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dtzrqf(m, n, a, lda, tau, info)
DTZRQF
Definition dtzrqf.f:136
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
Definition dcopy.f:82
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158
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