Contents


NAME

     cunmbr - VECT = 'Q', CUNMBR overwrites the  general  complex
     M-by-N matrix C with  SIDE = 'L' SIDE = 'R' TRANS = 'N'

SYNOPSIS

     SUBROUTINE CUNMBR(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
           WORK, LWORK, INFO)

     CHARACTER * 1 VECT, SIDE, TRANS
     COMPLEX A(LDA,*), TAU(*), C(LDC,*), WORK(*)
     INTEGER M, N, K, LDA, LDC, LWORK, INFO

     SUBROUTINE CUNMBR_64(VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
           WORK, LWORK, INFO)

     CHARACTER * 1 VECT, SIDE, TRANS
     COMPLEX A(LDA,*), TAU(*), C(LDC,*), WORK(*)
     INTEGER*8 M, N, K, LDA, LDC, LWORK, INFO

  F95 INTERFACE
     SUBROUTINE UNMBR(VECT, SIDE, [TRANS], [M], [N], K, A, [LDA], TAU, C,
            [LDC], [WORK], [LWORK], [INFO])

     CHARACTER(LEN=1) :: VECT, SIDE, TRANS
     COMPLEX, DIMENSION(:) :: TAU, WORK
     COMPLEX, DIMENSION(:,:) :: A, C
     INTEGER :: M, N, K, LDA, LDC, LWORK, INFO

     SUBROUTINE UNMBR_64(VECT, SIDE, [TRANS], [M], [N], K, A, [LDA], TAU,
            C, [LDC], [WORK], [LWORK], [INFO])

     CHARACTER(LEN=1) :: VECT, SIDE, TRANS
     COMPLEX, DIMENSION(:) :: TAU, WORK
     COMPLEX, DIMENSION(:,:) :: A, C
     INTEGER(8) :: M, N, K, LDA, LDC, LWORK, INFO

  C INTERFACE
     #include <sunperf.h>

     void cunmbr(char vect, char side, char trans, int m, int  n,
               int  k, complex *a, int lda, complex *tau, complex
               *c, int ldc, int *info);

     void cunmbr_64(char vect, char side,  char  trans,  long  m,
               long  n,  long  k,  complex  *a, long lda, complex
               *tau, complex *c, long ldc, long *info);

PURPOSE

     cunmbr 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 ele-
     mentary 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).

ARGUMENTS

     VECT (input)
               = 'Q': apply Q or Q**H;
               = 'P': apply P or P**H.

     SIDE (input)
               = 'L': apply Q, Q**H, P or P**H from the Left;
               = 'R': apply Q, Q**H, P or P**H from the Right.

     TRANS (input)
               = 'N':  No transpose, apply Q or P;
               = 'C':  Conjugate transpose, apply Q**H or P**H.

               TRANS is defaulted to 'N' for F95 INTERFACE.

     M (input) The number of rows of the matrix C. M >= 0.
     N (input) The number of columns of the matrix C. N >= 0.

     K (input) If VECT = 'Q', the number of columns in the origi-
               nal  matrix reduced by CGEBRD.  If VECT = 'P', the
               number of rows in the original matrix  reduced  by
               CGEBRD.  K >= 0.

     A (input) (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.

     LDA (input)
               The leading dimension of the array A.  If  VECT  =
               'Q',  LDA  >=  max(1,nq);  if  VECT  = 'P', LDA >=
               max(1,min(nq,K)).

     TAU (input)
               TAU(i) must contain the scalar factor of the  ele-
               mentary  reflector H(i) or G(i) which determines Q
               or P, as returned by CGEBRD in the array  argument
               TAUQ or TAUP.

     C (input/output)
               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.

     LDC (input)
               The leading dimension  of  the  array  C.  LDC  >=
               max(1,M).

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LWORK.

     LWORK (input)
               The dimension of the array WORK.  If SIDE  =  'L',
               LWORK  >=  max(1,N);  if  SIDE  =  'R',  LWORK  >=
               max(1,M).  For optimum performance LWORK  >=  N*NB
               if  SIDE  =  'L', and LWORK >= M*NB if SIDE = 'R',
               where NB is the optimal blocksize.

               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.

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value