Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cunmqr (3p)

Name

cunmqr - N matrix C with SIDE = 'L' SIDE = 'R' TRANS = 'N'

Synopsis

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

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

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

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




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

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

SUBROUTINE UNMQR_64(SIDE, TRANS, M, N, K, 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, K, LDA, LDC, LWORK, INFO




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           cunmqr(3P)



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


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

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

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

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




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

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

       SUBROUTINE UNMQR_64(SIDE, TRANS, M, N, K, 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, K, LDA, LDC, LWORK, INFO




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       cunmqr 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 defined as the product of k elemen-
       tary reflectors

             Q = H(1) H(2) . . . H(k)

       as  returned by CGEQRF. Q is of order M if SIDE = 'L' and of order N if
       SIDE = 'R'.


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


       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.


       K (input) The number of elementary reflectors whose product defines the
                 matrix  Q.  If SIDE = 'L', M >= K >= 0; if SIDE = 'R', N >= K
                 >= 0.


       A (input) The i-th column must contain the  vector  which  defines  the
                 elementary  reflector H(i), for i = 1,2,...,k, as returned by
                 CGEQRF in the first k columns of its array argument A.  A  is
                 modified by the routine but restored on exit.


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


       TAU (input)
                 TAU(i) must contain  the  scalar  factor  of  the  elementary
                 reflector H(i), as returned by CGEQRF.


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




                                  7 Nov 2015                        cunmqr(3P)