LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cunmbr.f
Go to the documentation of this file.
1*> \brief \b CUNMBR
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CUNMBR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cunmbr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cunmbr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cunmbr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CUNMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
20* LDC, WORK, LWORK, INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER SIDE, TRANS, VECT
24* INTEGER INFO, K, LDA, LDC, LWORK, M, N
25* ..
26* .. Array Arguments ..
27* COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ),
28* $ WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> If VECT = 'Q', CUNMBR overwrites the general complex M-by-N matrix C
38*> with
39*> SIDE = 'L' SIDE = 'R'
40*> TRANS = 'N': Q * C C * Q
41*> TRANS = 'C': Q**H * C C * Q**H
42*>
43*> If VECT = 'P', CUNMBR overwrites the general complex M-by-N matrix C
44*> with
45*> SIDE = 'L' SIDE = 'R'
46*> TRANS = 'N': P * C C * P
47*> TRANS = 'C': P**H * C C * P**H
48*>
49*> Here Q and P**H are the unitary matrices determined by CGEBRD when
50*> reducing a complex matrix A to bidiagonal form: A = Q * B * P**H. Q
51*> and P**H are defined as products of elementary reflectors H(i) and
52*> G(i) respectively.
53*>
54*> Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the
55*> order of the unitary matrix Q or P**H that is applied.
56*>
57*> If VECT = 'Q', A is assumed to have been an NQ-by-K matrix:
58*> if nq >= k, Q = H(1) H(2) . . . H(k);
59*> if nq < k, Q = H(1) H(2) . . . H(nq-1).
60*>
61*> If VECT = 'P', A is assumed to have been a K-by-NQ matrix:
62*> if k < nq, P = G(1) G(2) . . . G(k);
63*> if k >= nq, P = G(1) G(2) . . . G(nq-1).
64*> \endverbatim
65*
66* Arguments:
67* ==========
68*
69*> \param[in] VECT
70*> \verbatim
71*> VECT is CHARACTER*1
72*> = 'Q': apply Q or Q**H;
73*> = 'P': apply P or P**H.
74*> \endverbatim
75*>
76*> \param[in] SIDE
77*> \verbatim
78*> SIDE is CHARACTER*1
79*> = 'L': apply Q, Q**H, P or P**H from the Left;
80*> = 'R': apply Q, Q**H, P or P**H from the Right.
81*> \endverbatim
82*>
83*> \param[in] TRANS
84*> \verbatim
85*> TRANS is CHARACTER*1
86*> = 'N': No transpose, apply Q or P;
87*> = 'C': Conjugate transpose, apply Q**H or P**H.
88*> \endverbatim
89*>
90*> \param[in] M
91*> \verbatim
92*> M is INTEGER
93*> The number of rows of the matrix C. M >= 0.
94*> \endverbatim
95*>
96*> \param[in] N
97*> \verbatim
98*> N is INTEGER
99*> The number of columns of the matrix C. N >= 0.
100*> \endverbatim
101*>
102*> \param[in] K
103*> \verbatim
104*> K is INTEGER
105*> If VECT = 'Q', the number of columns in the original
106*> matrix reduced by CGEBRD.
107*> If VECT = 'P', the number of rows in the original
108*> matrix reduced by CGEBRD.
109*> K >= 0.
110*> \endverbatim
111*>
112*> \param[in] A
113*> \verbatim
114*> A is COMPLEX array, dimension
115*> (LDA,min(nq,K)) if VECT = 'Q'
116*> (LDA,nq) if VECT = 'P'
117*> The vectors which define the elementary reflectors H(i) and
118*> G(i), whose products determine the matrices Q and P, as
119*> returned by CGEBRD.
120*> \endverbatim
121*>
122*> \param[in] LDA
123*> \verbatim
124*> LDA is INTEGER
125*> The leading dimension of the array A.
126*> If VECT = 'Q', LDA >= max(1,nq);
127*> if VECT = 'P', LDA >= max(1,min(nq,K)).
128*> \endverbatim
129*>
130*> \param[in] TAU
131*> \verbatim
132*> TAU is COMPLEX array, dimension (min(nq,K))
133*> TAU(i) must contain the scalar factor of the elementary
134*> reflector H(i) or G(i) which determines Q or P, as returned
135*> by CGEBRD in the array argument TAUQ or TAUP.
136*> \endverbatim
137*>
138*> \param[in,out] C
139*> \verbatim
140*> C is COMPLEX array, dimension (LDC,N)
141*> On entry, the M-by-N matrix C.
142*> On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q
143*> or P*C or P**H*C or C*P or C*P**H.
144*> \endverbatim
145*>
146*> \param[in] LDC
147*> \verbatim
148*> LDC is INTEGER
149*> The leading dimension of the array C. LDC >= max(1,M).
150*> \endverbatim
151*>
152*> \param[out] WORK
153*> \verbatim
154*> WORK is COMPLEX array, dimension (MAX(1,LWORK))
155*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
156*> \endverbatim
157*>
158*> \param[in] LWORK
159*> \verbatim
160*> LWORK is INTEGER
161*> The dimension of the array WORK.
162*> If SIDE = 'L', LWORK >= max(1,N);
163*> if SIDE = 'R', LWORK >= max(1,M);
164*> if N = 0 or M = 0, LWORK >= 1.
165*> For optimum performance LWORK >= max(1,N*NB) if SIDE = 'L',
166*> and LWORK >= max(1,M*NB) if SIDE = 'R', where NB is the
167*> optimal blocksize. (NB = 0 if M = 0 or N = 0.)
168*>
169*> If LWORK = -1, then a workspace query is assumed; the routine
170*> only calculates the optimal size of the WORK array, returns
171*> this value as the first entry of the WORK array, and no error
172*> message related to LWORK is issued by XERBLA.
173*> \endverbatim
174*>
175*> \param[out] INFO
176*> \verbatim
177*> INFO is INTEGER
178*> = 0: successful exit
179*> < 0: if INFO = -i, the i-th argument had an illegal value
180*> \endverbatim
181*
182* Authors:
183* ========
184*
185*> \author Univ. of Tennessee
186*> \author Univ. of California Berkeley
187*> \author Univ. of Colorado Denver
188*> \author NAG Ltd.
189*
190*> \ingroup unmbr
191*
192* =====================================================================
193 SUBROUTINE cunmbr( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
194 $ LDC, WORK, LWORK, INFO )
195*
196* -- LAPACK computational routine --
197* -- LAPACK is a software package provided by Univ. of Tennessee, --
198* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
199*
200* .. Scalar Arguments ..
201 CHARACTER SIDE, TRANS, VECT
202 INTEGER INFO, K, LDA, LDC, LWORK, M, N
203* ..
204* .. Array Arguments ..
205 COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ),
206 $ work( * )
207* ..
208*
209* =====================================================================
210*
211* .. Local Scalars ..
212 LOGICAL APPLYQ, LEFT, LQUERY, NOTRAN
213 CHARACTER TRANST
214 INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
215* ..
216* .. External Functions ..
217 LOGICAL LSAME
218 INTEGER ILAENV
219 REAL SROUNDUP_LWORK
220 EXTERNAL ilaenv, lsame, sroundup_lwork
221* ..
222* .. External Subroutines ..
223 EXTERNAL cunmlq, cunmqr, xerbla
224* ..
225* .. Intrinsic Functions ..
226 INTRINSIC max, min
227* ..
228* .. Executable Statements ..
229*
230* Test the input arguments
231*
232 info = 0
233 applyq = lsame( vect, 'Q' )
234 left = lsame( side, 'L' )
235 notran = lsame( trans, 'N' )
236 lquery = ( lwork.EQ.-1 )
237*
238* NQ is the order of Q or P and NW is the minimum dimension of WORK
239*
240 IF( left ) THEN
241 nq = m
242 nw = max( 1, n )
243 ELSE
244 nq = n
245 nw = max( 1, m )
246 END IF
247 IF( .NOT.applyq .AND. .NOT.lsame( vect, 'P' ) ) THEN
248 info = -1
249 ELSE IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
250 info = -2
251 ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
252 info = -3
253 ELSE IF( m.LT.0 ) THEN
254 info = -4
255 ELSE IF( n.LT.0 ) THEN
256 info = -5
257 ELSE IF( k.LT.0 ) THEN
258 info = -6
259 ELSE IF( ( applyq .AND. lda.LT.max( 1, nq ) ) .OR.
260 $ ( .NOT.applyq .AND. lda.LT.max( 1, min( nq, k ) ) ) )
261 $ THEN
262 info = -8
263 ELSE IF( ldc.LT.max( 1, m ) ) THEN
264 info = -11
265 ELSE IF( lwork.LT.nw .AND. .NOT.lquery ) THEN
266 info = -13
267 END IF
268*
269 IF( info.EQ.0 ) THEN
270 IF( m.GT.0 .AND. n.GT.0 ) THEN
271 IF( applyq ) THEN
272 IF( left ) THEN
273 nb = ilaenv( 1, 'CUNMQR', side // trans, m-1, n,
274 $ m-1,
275 $ -1 )
276 ELSE
277 nb = ilaenv( 1, 'CUNMQR', side // trans, m, n-1,
278 $ n-1,
279 $ -1 )
280 END IF
281 ELSE
282 IF( left ) THEN
283 nb = ilaenv( 1, 'CUNMLQ', side // trans, m-1, n,
284 $ m-1,
285 $ -1 )
286 ELSE
287 nb = ilaenv( 1, 'CUNMLQ', side // trans, m, n-1,
288 $ n-1,
289 $ -1 )
290 END IF
291 END IF
292 lwkopt = nw*nb
293 ELSE
294 lwkopt = 1
295 END IF
296 work( 1 ) = sroundup_lwork(lwkopt)
297 END IF
298*
299 IF( info.NE.0 ) THEN
300 CALL xerbla( 'CUNMBR', -info )
301 RETURN
302 ELSE IF( lquery ) THEN
303 RETURN
304 END IF
305*
306* Quick return if possible
307*
308 IF( m.EQ.0 .OR. n.EQ.0 )
309 $ RETURN
310*
311 IF( applyq ) THEN
312*
313* Apply Q
314*
315 IF( nq.GE.k ) THEN
316*
317* Q was determined by a call to CGEBRD with nq >= k
318*
319 CALL cunmqr( side, trans, m, n, k, a, lda, tau, c, ldc,
320 $ work, lwork, iinfo )
321 ELSE IF( nq.GT.1 ) THEN
322*
323* Q was determined by a call to CGEBRD with nq < k
324*
325 IF( left ) THEN
326 mi = m - 1
327 ni = n
328 i1 = 2
329 i2 = 1
330 ELSE
331 mi = m
332 ni = n - 1
333 i1 = 1
334 i2 = 2
335 END IF
336 CALL cunmqr( side, trans, mi, ni, nq-1, a( 2, 1 ), lda,
337 $ tau,
338 $ c( i1, i2 ), ldc, work, lwork, iinfo )
339 END IF
340 ELSE
341*
342* Apply P
343*
344 IF( notran ) THEN
345 transt = 'C'
346 ELSE
347 transt = 'N'
348 END IF
349 IF( nq.GT.k ) THEN
350*
351* P was determined by a call to CGEBRD with nq > k
352*
353 CALL cunmlq( side, transt, m, n, k, a, lda, tau, c, ldc,
354 $ work, lwork, iinfo )
355 ELSE IF( nq.GT.1 ) THEN
356*
357* P was determined by a call to CGEBRD with nq <= k
358*
359 IF( left ) THEN
360 mi = m - 1
361 ni = n
362 i1 = 2
363 i2 = 1
364 ELSE
365 mi = m
366 ni = n - 1
367 i1 = 1
368 i2 = 2
369 END IF
370 CALL cunmlq( side, transt, mi, ni, nq-1, a( 1, 2 ), lda,
371 $ tau, c( i1, i2 ), ldc, work, lwork, iinfo )
372 END IF
373 END IF
374 work( 1 ) = sroundup_lwork(lwkopt)
375 RETURN
376*
377* End of CUNMBR
378*
379 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cunmbr(vect, side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
CUNMBR
Definition cunmbr.f:195
subroutine cunmlq(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
CUNMLQ
Definition cunmlq.f:166
subroutine cunmqr(side, trans, m, n, k, a, lda, tau, c, ldc, work, lwork, info)
CUNMQR
Definition cunmqr.f:166