LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zgemqrt.f
Go to the documentation of this file.
1*> \brief \b ZGEMQRT
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZGEMQRT + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgemqrt.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgemqrt.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgemqrt.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZGEMQRT( SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT,
20* C, LDC, WORK, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER SIDE, TRANS
24* INTEGER INFO, K, LDV, LDC, M, N, NB, LDT
25* ..
26* .. Array Arguments ..
27* COMPLEX*16 V( LDV, * ), C( LDC, * ), T( LDT, * ), WORK( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> ZGEMQRT overwrites the general complex M-by-N matrix C with
37*>
38*> SIDE = 'L' SIDE = 'R'
39*> TRANS = 'N': Q C C Q
40*> TRANS = 'C': Q**H C C Q**H
41*>
42*> where Q is a complex orthogonal matrix defined as the product of K
43*> elementary reflectors:
44*>
45*> Q = H(1) H(2) . . . H(K) = I - V T V**H
46*>
47*> generated using the compact WY representation as returned by ZGEQRT.
48*>
49*> Q is of order M if SIDE = 'L' and of order N if SIDE = 'R'.
50*> \endverbatim
51*
52* Arguments:
53* ==========
54*
55*> \param[in] SIDE
56*> \verbatim
57*> SIDE is CHARACTER*1
58*> = 'L': apply Q or Q**H from the Left;
59*> = 'R': apply Q or Q**H from the Right.
60*> \endverbatim
61*>
62*> \param[in] TRANS
63*> \verbatim
64*> TRANS is CHARACTER*1
65*> = 'N': No transpose, apply Q;
66*> = 'C': Conjugate transpose, apply Q**H.
67*> \endverbatim
68*>
69*> \param[in] M
70*> \verbatim
71*> M is INTEGER
72*> The number of rows of the matrix C. M >= 0.
73*> \endverbatim
74*>
75*> \param[in] N
76*> \verbatim
77*> N is INTEGER
78*> The number of columns of the matrix C. N >= 0.
79*> \endverbatim
80*>
81*> \param[in] K
82*> \verbatim
83*> K is INTEGER
84*> The number of elementary reflectors whose product defines
85*> the matrix Q.
86*> If SIDE = 'L', M >= K >= 0;
87*> if SIDE = 'R', N >= K >= 0.
88*> \endverbatim
89*>
90*> \param[in] NB
91*> \verbatim
92*> NB is INTEGER
93*> The block size used for the storage of T. K >= NB >= 1.
94*> This must be the same value of NB used to generate T
95*> in ZGEQRT.
96*> \endverbatim
97*>
98*> \param[in] V
99*> \verbatim
100*> V is COMPLEX*16 array, dimension (LDV,K)
101*> The i-th column must contain the vector which defines the
102*> elementary reflector H(i), for i = 1,2,...,k, as returned by
103*> ZGEQRT in the first K columns of its array argument A.
104*> \endverbatim
105*>
106*> \param[in] LDV
107*> \verbatim
108*> LDV is INTEGER
109*> The leading dimension of the array V.
110*> If SIDE = 'L', LDA >= max(1,M);
111*> if SIDE = 'R', LDA >= max(1,N).
112*> \endverbatim
113*>
114*> \param[in] T
115*> \verbatim
116*> T is COMPLEX*16 array, dimension (LDT,K)
117*> The upper triangular factors of the block reflectors
118*> as returned by ZGEQRT, stored as a NB-by-N matrix.
119*> \endverbatim
120*>
121*> \param[in] LDT
122*> \verbatim
123*> LDT is INTEGER
124*> The leading dimension of the array T. LDT >= NB.
125*> \endverbatim
126*>
127*> \param[in,out] C
128*> \verbatim
129*> C is COMPLEX*16 array, dimension (LDC,N)
130*> On entry, the M-by-N matrix C.
131*> On exit, C is overwritten by Q C, Q**H C, C Q**H or C Q.
132*> \endverbatim
133*>
134*> \param[in] LDC
135*> \verbatim
136*> LDC is INTEGER
137*> The leading dimension of the array C. LDC >= max(1,M).
138*> \endverbatim
139*>
140*> \param[out] WORK
141*> \verbatim
142*> WORK is COMPLEX*16 array. The dimension of WORK is
143*> N*NB if SIDE = 'L', or M*NB if SIDE = 'R'.
144*> \endverbatim
145*>
146*> \param[out] INFO
147*> \verbatim
148*> INFO is INTEGER
149*> = 0: successful exit
150*> < 0: if INFO = -i, the i-th argument had an illegal value
151*> \endverbatim
152*
153* Authors:
154* ========
155*
156*> \author Univ. of Tennessee
157*> \author Univ. of California Berkeley
158*> \author Univ. of Colorado Denver
159*> \author NAG Ltd.
160*
161*> \ingroup gemqrt
162*
163* =====================================================================
164 SUBROUTINE zgemqrt( SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT,
165 $ C, LDC, WORK, INFO )
166*
167* -- LAPACK computational routine --
168* -- LAPACK is a software package provided by Univ. of Tennessee, --
169* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
170*
171* .. Scalar Arguments ..
172 CHARACTER SIDE, TRANS
173 INTEGER INFO, K, LDV, LDC, M, N, NB, LDT
174* ..
175* .. Array Arguments ..
176 COMPLEX*16 V( LDV, * ), C( LDC, * ), T( LDT, * ), WORK( * )
177* ..
178*
179* =====================================================================
180*
181* ..
182* .. Local Scalars ..
183 LOGICAL LEFT, RIGHT, TRAN, NOTRAN
184 INTEGER I, IB, LDWORK, KF, Q
185* ..
186* .. External Functions ..
187 LOGICAL LSAME
188 EXTERNAL lsame
189* ..
190* .. External Subroutines ..
191 EXTERNAL xerbla, zlarfb
192* ..
193* .. Intrinsic Functions ..
194 INTRINSIC max, min
195* ..
196* .. Executable Statements ..
197*
198* .. Test the input arguments ..
199*
200 info = 0
201 left = lsame( side, 'L' )
202 right = lsame( side, 'R' )
203 tran = lsame( trans, 'C' )
204 notran = lsame( trans, 'N' )
205*
206 IF( left ) THEN
207 ldwork = max( 1, n )
208 q = m
209 ELSE IF ( right ) THEN
210 ldwork = max( 1, m )
211 q = n
212 END IF
213 IF( .NOT.left .AND. .NOT.right ) THEN
214 info = -1
215 ELSE IF( .NOT.tran .AND. .NOT.notran ) THEN
216 info = -2
217 ELSE IF( m.LT.0 ) THEN
218 info = -3
219 ELSE IF( n.LT.0 ) THEN
220 info = -4
221 ELSE IF( k.LT.0 .OR. k.GT.q ) THEN
222 info = -5
223 ELSE IF( nb.LT.1 .OR. (nb.GT.k .AND. k.GT.0)) THEN
224 info = -6
225 ELSE IF( ldv.LT.max( 1, q ) ) THEN
226 info = -8
227 ELSE IF( ldt.LT.nb ) THEN
228 info = -10
229 ELSE IF( ldc.LT.max( 1, m ) ) THEN
230 info = -12
231 END IF
232*
233 IF( info.NE.0 ) THEN
234 CALL xerbla( 'ZGEMQRT', -info )
235 RETURN
236 END IF
237*
238* .. Quick return if possible ..
239*
240 IF( m.EQ.0 .OR. n.EQ.0 .OR. k.EQ.0 ) RETURN
241*
242 IF( left .AND. tran ) THEN
243*
244 DO i = 1, k, nb
245 ib = min( nb, k-i+1 )
246 CALL zlarfb( 'L', 'C', 'F', 'C', m-i+1, n, ib,
247 $ v( i, i ), ldv, t( 1, i ), ldt,
248 $ c( i, 1 ), ldc, work, ldwork )
249 END DO
250*
251 ELSE IF( right .AND. notran ) THEN
252*
253 DO i = 1, k, nb
254 ib = min( nb, k-i+1 )
255 CALL zlarfb( 'R', 'N', 'F', 'C', m, n-i+1, ib,
256 $ v( i, i ), ldv, t( 1, i ), ldt,
257 $ c( 1, i ), ldc, work, ldwork )
258 END DO
259*
260 ELSE IF( left .AND. notran ) THEN
261*
262 kf = ((k-1)/nb)*nb+1
263 DO i = kf, 1, -nb
264 ib = min( nb, k-i+1 )
265 CALL zlarfb( 'L', 'N', 'F', 'C', m-i+1, n, ib,
266 $ v( i, i ), ldv, t( 1, i ), ldt,
267 $ c( i, 1 ), ldc, work, ldwork )
268 END DO
269*
270 ELSE IF( right .AND. tran ) THEN
271*
272 kf = ((k-1)/nb)*nb+1
273 DO i = kf, 1, -nb
274 ib = min( nb, k-i+1 )
275 CALL zlarfb( 'R', 'C', 'F', 'C', m, n-i+1, ib,
276 $ v( i, i ), ldv, t( 1, i ), ldt,
277 $ c( 1, i ), ldc, work, ldwork )
278 END DO
279*
280 END IF
281*
282 RETURN
283*
284* End of ZGEMQRT
285*
286 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgemqrt(side, trans, m, n, k, nb, v, ldv, t, ldt, c, ldc, work, info)
ZGEMQRT
Definition zgemqrt.f:166
subroutine zlarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)
ZLARFB applies a block reflector or its conjugate-transpose to a general rectangular matrix.
Definition zlarfb.f:195