Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cunm2l (3p)

Name

cunm2l - torization determined by cgeqlf (unblocked algorithm)

Synopsis

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


CHARACTER*1 SIDE, TRANS

INTEGER INFO, K, LDA, LDC, M, N

COMPLEX A(LDA,*), C(LDC,*), TAU(*), WORK(*)


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


CHARACTER*1 SIDE, TRANS

INTEGER*8 INFO, K, LDA, LDC, M, N

COMPLEX A(LDA,*), C(LDC,*), TAU(*), WORK(*)


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


INTEGER :: M, N, K, LDA, LDC, INFO

CHARACTER(LEN=1) :: SIDE, TRANS

COMPLEX, DIMENSION(:) :: TAU, WORK

COMPLEX, DIMENSION(:,:) :: A, C


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


INTEGER(8) :: M, N, K, LDA, LDC, INFO

CHARACTER(LEN=1) :: SIDE, TRANS

COMPLEX, DIMENSION(:) :: TAU, WORK

COMPLEX, DIMENSION(:,:) :: A, C


C INTERFACE
#include <sunperf.h>

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


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

Description

Oracle Solaris Studio Performance Library                           cunm2l(3P)



NAME
       cunm2l - multiply a general matrix by the unitary matrix from a QL fac-
       torization determined by cgeqlf (unblocked algorithm)


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


       CHARACTER*1 SIDE, TRANS

       INTEGER INFO, K, LDA, LDC, M, N

       COMPLEX A(LDA,*), C(LDC,*), TAU(*), WORK(*)


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


       CHARACTER*1 SIDE, TRANS

       INTEGER*8 INFO, K, LDA, LDC, M, N

       COMPLEX A(LDA,*), C(LDC,*), TAU(*), WORK(*)


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


       INTEGER :: M, N, K, LDA, LDC, INFO

       CHARACTER(LEN=1) :: SIDE, TRANS

       COMPLEX, DIMENSION(:) :: TAU, WORK

       COMPLEX, DIMENSION(:,:) :: A, C


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


       INTEGER(8) :: M, N, K, LDA, LDC, INFO

       CHARACTER(LEN=1) :: SIDE, TRANS

       COMPLEX, DIMENSION(:) :: TAU, WORK

       COMPLEX, DIMENSION(:,:) :: A, C


   C INTERFACE
       #include <sunperf.h>

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


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


PURPOSE
       cunm2l overwrites the general complex m-by-n matrix C with
       Q * C  if SIDE = 'L' and TRANS = 'N', or
       Q**H * C  if SIDE = 'L' and TRANS = 'C', or
       C * Q  if SIDE = 'R' and TRANS = 'N', or
       C * Q**H if SIDE = 'R' and TRANS = 'C',
       where Q is a complex unitary matrix defined as the product of k elemen-
       tary reflectors
       Q = H(k) . . . H(2) H(1)
       as  returned by CGEQLF. Q is of order m if SIDE = 'L' and of order n if
       SIDE = 'R'.


ARGUMENTS
       SIDE (input)
                 SIDE is CHARACTER*1
                 = 'L': apply Q or Q**H from the Left
                 = 'R': apply Q or Q**H from the Right


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


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


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


       K (input)
                 K is INTEGER
                 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)
                 A is COMPLEX array, dimension (LDA,K)
                 The  i-th  column  must  contain the vector which defines the
                 elementary reflector H(i), for i = 1,2,...,k, as returned  by
                 CGEQLF  in  the last k columns of its array argument A.  A is
                 modified by the routine but restored on exit.


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


       TAU (input)
                 TAU is COMPLEX array, dimension (K)
                 TAU(i) must contain  the  scalar  factor  of  the  elementary
                 reflector H(i), as returned by CGEQLF.


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


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


       WORK (output)
                 WORK is COMPLEX array, dimension
                 (N) if SIDE = 'L',
                 (M) if SIDE = 'R'


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




                                  7 Nov 2015                        cunm2l(3P)