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

ZUNMBR

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

Purpose:
 If VECT = 'Q', ZUNMBR 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', ZUNMBR 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 ZGEBRD 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 ZGEBRD.
          If VECT = 'P', the number of rows in the original
          matrix reduced by ZGEBRD.
          K >= 0.
[in]A
          A is COMPLEX*16 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 ZGEBRD.
[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*16 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 ZGEBRD in the array argument TAUQ or TAUP.
[in,out]C
          C is COMPLEX*16 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*16 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 198 of file zunmbr.f.

198 *
199 * -- LAPACK computational routine (version 3.4.0) --
200 * -- LAPACK is a software package provided by Univ. of Tennessee, --
201 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
202 * November 2011
203 *
204 * .. Scalar Arguments ..
205  CHARACTER side, trans, vect
206  INTEGER info, k, lda, ldc, lwork, m, n
207 * ..
208 * .. Array Arguments ..
209  COMPLEX*16 a( lda, * ), c( ldc, * ), tau( * ), work( * )
210 * ..
211 *
212 * =====================================================================
213 *
214 * .. Local Scalars ..
215  LOGICAL applyq, left, lquery, notran
216  CHARACTER transt
217  INTEGER i1, i2, iinfo, lwkopt, mi, nb, ni, nq, nw
218 * ..
219 * .. External Functions ..
220  LOGICAL lsame
221  INTEGER ilaenv
222  EXTERNAL lsame, ilaenv
223 * ..
224 * .. External Subroutines ..
225  EXTERNAL xerbla, zunmlq, zunmqr
226 * ..
227 * .. Intrinsic Functions ..
228  INTRINSIC max, min
229 * ..
230 * .. Executable Statements ..
231 *
232 * Test the input arguments
233 *
234  info = 0
235  applyq = lsame( vect, 'Q' )
236  left = lsame( side, 'L' )
237  notran = lsame( trans, 'N' )
238  lquery = ( lwork.EQ.-1 )
239 *
240 * NQ is the order of Q or P and NW is the minimum dimension of WORK
241 *
242  IF( left ) THEN
243  nq = m
244  nw = n
245  ELSE
246  nq = n
247  nw = m
248  END IF
249  IF( m.EQ.0 .OR. n.EQ.0 ) THEN
250  nw = 0
251  END IF
252  IF( .NOT.applyq .AND. .NOT.lsame( vect, 'P' ) ) THEN
253  info = -1
254  ELSE IF( .NOT.left .AND. .NOT.lsame( side, 'R' ) ) THEN
255  info = -2
256  ELSE IF( .NOT.notran .AND. .NOT.lsame( trans, 'C' ) ) THEN
257  info = -3
258  ELSE IF( m.LT.0 ) THEN
259  info = -4
260  ELSE IF( n.LT.0 ) THEN
261  info = -5
262  ELSE IF( k.LT.0 ) THEN
263  info = -6
264  ELSE IF( ( applyq .AND. lda.LT.max( 1, nq ) ) .OR.
265  $ ( .NOT.applyq .AND. lda.LT.max( 1, min( nq, k ) ) ) )
266  $ THEN
267  info = -8
268  ELSE IF( ldc.LT.max( 1, m ) ) THEN
269  info = -11
270  ELSE IF( lwork.LT.max( 1, nw ) .AND. .NOT.lquery ) THEN
271  info = -13
272  END IF
273 *
274  IF( info.EQ.0 ) THEN
275  IF( nw.GT.0 ) THEN
276  IF( applyq ) THEN
277  IF( left ) THEN
278  nb = ilaenv( 1, 'ZUNMQR', side // trans, m-1, n, m-1,
279  $ -1 )
280  ELSE
281  nb = ilaenv( 1, 'ZUNMQR', side // trans, m, n-1, n-1,
282  $ -1 )
283  END IF
284  ELSE
285  IF( left ) THEN
286  nb = ilaenv( 1, 'ZUNMLQ', side // trans, m-1, n, m-1,
287  $ -1 )
288  ELSE
289  nb = ilaenv( 1, 'ZUNMLQ', side // trans, m, n-1, n-1,
290  $ -1 )
291  END IF
292  END IF
293  lwkopt = max( 1, nw*nb )
294  ELSE
295  lwkopt = 1
296  END IF
297  work( 1 ) = lwkopt
298  END IF
299 *
300  IF( info.NE.0 ) THEN
301  CALL xerbla( 'ZUNMBR', -info )
302  RETURN
303  ELSE IF( lquery ) THEN
304  RETURN
305  END IF
306 *
307 * Quick return if possible
308 *
309  IF( m.EQ.0 .OR. n.EQ.0 )
310  $ RETURN
311 *
312  IF( applyq ) THEN
313 *
314 * Apply Q
315 *
316  IF( nq.GE.k ) THEN
317 *
318 * Q was determined by a call to ZGEBRD with nq >= k
319 *
320  CALL zunmqr( side, trans, m, n, k, a, lda, tau, c, ldc,
321  $ work, lwork, iinfo )
322  ELSE IF( nq.GT.1 ) THEN
323 *
324 * Q was determined by a call to ZGEBRD with nq < k
325 *
326  IF( left ) THEN
327  mi = m - 1
328  ni = n
329  i1 = 2
330  i2 = 1
331  ELSE
332  mi = m
333  ni = n - 1
334  i1 = 1
335  i2 = 2
336  END IF
337  CALL zunmqr( side, trans, mi, ni, nq-1, a( 2, 1 ), lda, 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 ZGEBRD with nq > k
352 *
353  CALL zunmlq( 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 ZGEBRD 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 zunmlq( 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 ) = lwkopt
375  RETURN
376 *
377 * End of ZUNMBR
378 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zunmqr(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
ZUNMQR
Definition: zunmqr.f:169
subroutine zunmlq(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
ZUNMLQ
Definition: zunmlq.f:169
integer function ilaenv(ISPEC, NAME, OPTS, N1, N2, N3, N4)
Definition: tstiee.f:83
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: