3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CUNMBR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cunmbr.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cunmbr.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cunmbr.f">
21 * SUBROUTINE CUNMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
22 * LDC, WORK, LWORK, INFO )
24 * .. Scalar Arguments ..
25 * CHARACTER SIDE, TRANS, VECT
26 * INTEGER INFO, K, LDA, LDC, LWORK, M, N
28 * .. Array Arguments ..
29 * COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ),
39 *> If VECT = 'Q', CUNMBR overwrites the general complex M-by-N matrix C
41 *> SIDE = 'L' SIDE = 'R'
42 *> TRANS = 'N': Q * C C * Q
43 *> TRANS = 'C': Q**H * C C * Q**H
45 *> If VECT = 'P', CUNMBR overwrites the general complex M-by-N matrix C
47 *> SIDE = 'L' SIDE = 'R'
48 *> TRANS = 'N': P * C C * P
49 *> TRANS = 'C': P**H * C C * P**H
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
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.
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).
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).
73 *> VECT is CHARACTER*1
74 *> = 'Q': apply Q or Q**H;
75 *> = 'P': apply P or P**H.
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.
87 *> TRANS is CHARACTER*1
88 *> = 'N': No transpose, apply Q or P;
89 *> = 'C': Conjugate transpose, apply Q**H or P**H.
95 *> The number of rows of the matrix C. M >= 0.
101 *> The number of columns of the matrix C. N >= 0.
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.
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.
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)).
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.
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.
151 *> The leading dimension of the array C. LDC >= max(1,M).
156 *> WORK is COMPLEX array, dimension (MAX(1,LWORK))
157 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
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.)
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.
180 *> = 0: successful exit
181 *> < 0: if INFO = -i, the i-th argument had an illegal value
187 *> \author Univ. of Tennessee
188 *> \author Univ. of California Berkeley
189 *> \author Univ. of Colorado Denver
192 *> \date November 2011
194 *> \ingroup complexOTHERcomputational
196 * =====================================================================
197 SUBROUTINE CUNMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C,
198 $ LDC, WORK, LWORK, INFO )
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..--
205 * .. Scalar Arguments ..
206 CHARACTER SIDE, TRANS, VECT
207 INTEGER INFO, K, LDA, LDC, LWORK, M, N
209 * .. Array Arguments ..
210 COMPLEX A( LDA, * ), C( LDC, * ), TAU( * ),
214 * =====================================================================
216 * .. Local Scalars ..
217 LOGICAL APPLYQ, LEFT, LQUERY, NOTRAN
219 INTEGER I1, I2, IINFO, LWKOPT, MI, NB, NI, NQ, NW
221 * .. External Functions ..
224 EXTERNAL ILAENV, LSAME
226 * .. External Subroutines ..
227 EXTERNAL CUNMLQ, CUNMQR, XERBLA
229 * .. Intrinsic Functions ..
232 * .. Executable Statements ..
234 * Test the input arguments
237 APPLYQ = LSAME( VECT, 'Q' )
238 LEFT = LSAME( SIDE, 'L' )
239 NOTRAN = LSAME( TRANS, 'N' )
240 LQUERY = ( LWORK.EQ.-1 )
242 * NQ is the order of Q or P and NW is the minimum dimension of WORK
251 IF( M.EQ.0 .OR. N.EQ.0 ) THEN
254 IF( .NOT.APPLYQ .AND. .NOT.LSAME( VECT, 'P' ) ) THEN
256 ELSE IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
258 ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
260 ELSE IF( M.LT.0 ) THEN
262 ELSE IF( N.LT.0 ) THEN
264 ELSE IF( K.LT.0 ) THEN
266 ELSE IF( ( APPLYQ .AND. LDA.LT.MAX( 1, NQ ) ) .OR.
267 $ ( .NOT.APPLYQ .AND. LDA.LT.MAX( 1, MIN( NQ, K ) ) ) )
270 ELSE IF( LDC.LT.MAX( 1, M ) ) THEN
272 ELSE IF( LWORK.LT.MAX( 1, NW ) .AND. .NOT.LQUERY ) THEN
280 NB = ILAENV( 1, 'CUNMQR', SIDE // TRANS, M-1, N, M-1,
283 NB = ILAENV( 1, 'CUNMQR', SIDE // TRANS, M, N-1, N-1,
288 NB = ILAENV( 1, 'CUNMLQ', SIDE // TRANS, M-1, N, M-1,
291 NB = ILAENV( 1, 'CUNMLQ', SIDE // TRANS, M, N-1, N-1,
295 LWKOPT = MAX( 1, NW*NB )
303 CALL XERBLA( 'CUNMBR', -INFO )
305 ELSE IF( LQUERY ) THEN
309 * Quick return if possible
311 IF( M.EQ.0 .OR. N.EQ.0 )
320 * Q was determined by a call to CGEBRD with nq >= k
322 CALL CUNMQR( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
323 $ WORK, LWORK, IINFO )
324 ELSE IF( NQ.GT.1 ) THEN
326 * Q was determined by a call to CGEBRD with nq < k
339 CALL CUNMQR( SIDE, TRANS, MI, NI, NQ-1, A( 2, 1 ), LDA, TAU,
340 $ C( I1, I2 ), LDC, WORK, LWORK, IINFO )
353 * P was determined by a call to CGEBRD with nq > k
355 CALL CUNMLQ( SIDE, TRANST, M, N, K, A, LDA, TAU, C, LDC,
356 $ WORK, LWORK, IINFO )
357 ELSE IF( NQ.GT.1 ) THEN
359 * P was determined by a call to CGEBRD with nq <= k
372 CALL CUNMLQ( SIDE, TRANST, MI, NI, NQ-1, A( 1, 2 ), LDA,
373 $ TAU, C( I1, I2 ), LDC, WORK, LWORK, IINFO )