Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cunmtr (3p)

Name

cunmtr - N matrix C with Q*C, or Q**H*C, or C*Q**H, or C*Q, where Q is defined as the product of elemen- tary reflectors, as returned by CHETRD

Synopsis

SUBROUTINE CUNMTR(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C, LDC, WORK,
LWORK, INFO)

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

SUBROUTINE CUNMTR_64(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C, LDC,
WORK, LWORK, INFO)

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




F95 INTERFACE
SUBROUTINE UNMTR(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C,
LDC, WORK, LWORK, INFO)

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

SUBROUTINE UNMTR_64(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C,
LDC, WORK, LWORK, INFO)

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




C INTERFACE
#include <sunperf.h>

void cunmtr(char side, char uplo, char trans, int m, int n, complex *a,
int lda, complex *tau, complex *c, int ldc, int *info);

void cunmtr_64(char side, char uplo, char trans, long m, long  n,  com-
plex  *a,  long lda, complex *tau, complex *c, long ldc, long
*info);

Description

Oracle Solaris Studio Performance Library                           cunmtr(3P)



NAME
       cunmtr  -  overwrite  the  general complex M-by-N matrix C with Q*C, or
       Q**H*C, or C*Q**H, or C*Q, where Q is defined as the product of elemen-
       tary reflectors, as returned by CHETRD


SYNOPSIS
       SUBROUTINE CUNMTR(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C, LDC, WORK,
             LWORK, INFO)

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

       SUBROUTINE CUNMTR_64(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C, LDC,
             WORK, LWORK, INFO)

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




   F95 INTERFACE
       SUBROUTINE UNMTR(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C,
              LDC, WORK, LWORK, INFO)

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

       SUBROUTINE UNMTR_64(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C,
              LDC, WORK, LWORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void cunmtr(char side, char uplo, char trans, int m, int n, complex *a,
                 int lda, complex *tau, complex *c, int ldc, int *info);

       void cunmtr_64(char side, char uplo, char trans, long m, long  n,  com-
                 plex  *a,  long lda, complex *tau, complex *c, long ldc, long
                 *info);



PURPOSE
       cunmtr 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

       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 nq-1 ele-
       mentary reflectors, as returned by CHETRD:

       if UPLO = 'U', Q = H(nq-1) . . . H(2) * H(1);

       if UPLO = 'L', Q = H(1) * H(2) . . . H(nq-1).


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


       UPLO (input)
                 = 'U': Upper triangle of  A  contains  elementary  reflectors
                 from CHETRD;
                 =  'L':  Lower  triangle  of A contains elementary reflectors
                 from CHETRD.


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


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


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


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


       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)
                 dimension
                 (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 CHETRD.


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


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


       WORK (workspace)
                 dimension (LWORK)
                 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 block-
                 size.

                 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 illegal value



                                  7 Nov 2015                        cunmtr(3P)