Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zunml2 (3p)

Name

zunml2 - torization determined by cgelqf (unblocked algorithm)

Synopsis

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

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

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

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




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

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           zunml2(3P)



NAME
       zunml2 - multiply a general matrix by the unitary matrix from a LQ fac-
       torization determined by cgelqf (unblocked algorithm)


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

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

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

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




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

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

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



PURPOSE
       zunml2 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 . . . H(2)**H * H(1)**H
       as  returned by ZGELQF. Q is of order M if SIDE = 'L' and of order N if
       SIDE = 'R'.


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


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


       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) (LDA,M) if SIDE = 'L', (LDA,N) if SIDE =  'R'  The  i-th  row
                 must  contain the vector which defines the elementary reflec-
                 tor H(i), for i = 1,2,...,k, as returned  by  ZGELQF  in  the
                 first  k  rows of its array argument A.  A is modified by the
                 routine but restored on exit.


       LDA (input)
                 The leading dimension of the array A. LDA >= max(1,K).


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


       C (input/output)
                 On  entry, the m-by-n matrix C.  On exit, C is overwritten by
                 Q*C or Q'*C or C*Q' or C*Q.


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


       WORK (workspace)
                 (N) if SIDE = 'L', (M) if SIDE = 'R'


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




                                  7 Nov 2015                        zunml2(3P)