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