LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cunmbr ( character  VECT,
character  SIDE,
character  TRANS,
integer  M,
integer  N,
integer  K,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( * )  TAU,
complex, dimension( ldc, * )  C,
integer  LDC,
complex, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

CUNMBR

Download CUNMBR + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 If VECT = 'Q', CUNMBR overwrites the general complex M-by-N matrix C
 with
                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      Q * C          C * Q
 TRANS = 'C':      Q**H * C       C * Q**H

 If VECT = 'P', CUNMBR overwrites the general complex M-by-N matrix C
 with
                 SIDE = 'L'     SIDE = 'R'
 TRANS = 'N':      P * C          C * P
 TRANS = 'C':      P**H * C       C * P**H

 Here Q and P**H are the unitary matrices determined by CGEBRD when
 reducing a complex matrix A to bidiagonal form: A = Q * B * P**H. Q
 and P**H are defined as products of elementary reflectors H(i) and
 G(i) respectively.

 Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the
 order of the unitary matrix Q or P**H that is applied.

 If VECT = 'Q', A is assumed to have been an NQ-by-K matrix:
 if nq >= k, Q = H(1) H(2) . . . H(k);
 if nq < k, Q = H(1) H(2) . . . H(nq-1).

 If VECT = 'P', A is assumed to have been a K-by-NQ matrix:
 if k < nq, P = G(1) G(2) . . . G(k);
 if k >= nq, P = G(1) G(2) . . . G(nq-1).
Parameters
[in]VECT
          VECT is CHARACTER*1
          = 'Q': apply Q or Q**H;
          = 'P': apply P or P**H.
[in]SIDE
          SIDE is CHARACTER*1
          = 'L': apply Q, Q**H, P or P**H from the Left;
          = 'R': apply Q, Q**H, P or P**H from the Right.
[in]TRANS
          TRANS is CHARACTER*1
          = 'N':  No transpose, apply Q or P;
          = 'C':  Conjugate transpose, apply Q**H or P**H.
[in]M
          M is INTEGER
          The number of rows of the matrix C. M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix C. N >= 0.
[in]K
          K is INTEGER
          If VECT = 'Q', the number of columns in the original
          matrix reduced by CGEBRD.
          If VECT = 'P', the number of rows in the original
          matrix reduced by CGEBRD.
          K >= 0.
[in]A
          A is COMPLEX array, dimension
                                (LDA,min(nq,K)) if VECT = 'Q'
                                (LDA,nq)        if VECT = 'P'
          The vectors which define the elementary reflectors H(i) and
          G(i), whose products determine the matrices Q and P, as
          returned by CGEBRD.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.
          If VECT = 'Q', LDA >= max(1,nq);
          if VECT = 'P', LDA >= max(1,min(nq,K)).
[in]TAU
          TAU is COMPLEX array, dimension (min(nq,K))
          TAU(i) must contain the scalar factor of the elementary
          reflector H(i) or G(i) which determines Q or P, as returned
          by CGEBRD in the array argument TAUQ or TAUP.
[in,out]C
          C is COMPLEX array, dimension (LDC,N)
          On entry, the M-by-N matrix C.
          On exit, C is overwritten by Q*C or Q**H*C or C*Q**H or C*Q
          or P*C or P**H*C or C*P or C*P**H.
[in]LDC
          LDC is INTEGER
          The leading dimension of the array C. LDC >= max(1,M).
[out]WORK
          WORK is COMPLEX array, dimension (MAX(1,LWORK))
          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK.
          If SIDE = 'L', LWORK >= max(1,N);
          if SIDE = 'R', LWORK >= max(1,M);
          if N = 0 or M = 0, LWORK >= 1.
          For optimum performance LWORK >= max(1,N*NB) if SIDE = 'L',
          and LWORK >= max(1,M*NB) if SIDE = 'R', where NB is the
          optimal blocksize. (NB = 0 if M = 0 or N = 0.)

          If LWORK = -1, then a workspace query is assumed; the routine
          only calculates the optimal size of the WORK array, returns
          this value as the first entry of the WORK array, and no error
          message related to LWORK is issued by XERBLA.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 199 of file cunmbr.f.

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 *
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
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83
subroutine cunmlq(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
CUNMLQ
Definition: cunmlq.f:170
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: