Contents


NAME

     cunmhr - overwrite the general complex M-by-N matrix C  with
     SIDE = 'L' SIDE = 'R' TRANS = 'N'

SYNOPSIS

     SUBROUTINE CUNMHR(SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C, LDC,
           WORK, LWORK, INFO)

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

     SUBROUTINE CUNMHR_64(SIDE, TRANS, M, N, ILO, IHI, A, LDA, TAU, C,
           LDC, WORK, LWORK, INFO)

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

  F95 INTERFACE
     SUBROUTINE UNMHR(SIDE, [TRANS], [M], [N], ILO, IHI, A, [LDA], TAU, C,
            [LDC], [WORK], [LWORK], [INFO])

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

     SUBROUTINE UNMHR_64(SIDE, [TRANS], [M], [N], ILO, IHI, A, [LDA], TAU,
            C, [LDC], [WORK], [LWORK], [INFO])

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

  C INTERFACE
     #include <sunperf.h>

     void cunmhr(char side, char trans, int m, int  n,  int  ilo,
               int  ihi,  complex *a, int lda, complex *tau, com-
               plex *c, int ldc, int *info);

     void cunmhr_64(char side, char trans, long m, long  n,  long
               ilo, long ihi, complex *a, long lda, complex *tau,
               complex *c, long ldc, long *info);

PURPOSE

     cunmhr overwrites the general complex M-by-N matrix  C  with
     TRANS = 'C':      Q**H * C       C * Q**H

     where Q is a complex unitary matrix of order nq, with nq = m
     if  SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the
     product of IHI-ILO elementary  reflectors,  as  returned  by
     CGEHRD:

     Q = H(ilo) H(ilo+1) . . . H(ihi-1).

ARGUMENTS

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

     TRANS (input)
               = 'N': apply Q  (No transpose)
               = 'C': apply Q**H (Conjugate transpose)

               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.

     ILO (input)
               ILO and IHI must have the same values  as  in  the
               previous  call  of  CGEHRD. Q is equal to the unit
               matrix      except      in      the      submatrix
               Q(ilo+1:ihi,ilo+1:ihi).   If SIDE = 'L', then 1 <=
               ILO <= IHI <= M, if M > 0, and ILO = 1 and  IHI  =
               0,  if  M = 0; if SIDE = 'R', then 1 <= ILO <= IHI
               <= N, if N > 0, and ILO = 1 and IHI = 0, if N = 0.

     IHI (input)
               See the description of ILO.

     A (input) (LDA,M) if SIDE = 'L' (LDA,N) if SIDE  =  'R'  The
               vectors which define the elementary reflectors, as
               returned by CGEHRD.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               max(1,M)  if SIDE = 'L'; LDA >= max(1,N) if SIDE =
               'R'.

     TAU (input)
               (M-1) if SIDE = 'L' (N-1) if  SIDE  =  'R'  TAU(i)
               must  contain  the scalar factor of the elementary
               reflector H(i), as returned by CGEHRD.

     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.

     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