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