Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zupmtr (3p)

Name

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

Synopsis

SUBROUTINE ZUPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
INFO)

CHARACTER*1 SIDE, UPLO, TRANS
DOUBLE COMPLEX AP(*), TAU(*), C(LDC,*), WORK(*)
INTEGER M, N, LDC, INFO

SUBROUTINE ZUPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
INFO)

CHARACTER*1 SIDE, UPLO, TRANS
DOUBLE COMPLEX AP(*), TAU(*), C(LDC,*), WORK(*)
INTEGER*8 M, N, LDC, INFO




F95 INTERFACE
SUBROUTINE UPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
WORK, INFO)

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

SUBROUTINE UPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
WORK, INFO)

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




C INTERFACE
#include <sunperf.h>

void zupmtr(char side, char uplo, char trans, int m, int n,  doublecom-
plex  *ap, doublecomplex *tau, doublecomplex *c, int ldc, int
*info);

void zupmtr_64(char side, char uplo, char trans, long m, long  n,  dou-
blecomplex  *ap,  doublecomplex  *tau, doublecomplex *c, long
ldc, long *info);

Description

Oracle Solaris Studio Performance Library                           zupmtr(3P)



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


SYNOPSIS
       SUBROUTINE ZUPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
             INFO)

       CHARACTER*1 SIDE, UPLO, TRANS
       DOUBLE COMPLEX AP(*), TAU(*), C(LDC,*), WORK(*)
       INTEGER M, N, LDC, INFO

       SUBROUTINE ZUPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK,
             INFO)

       CHARACTER*1 SIDE, UPLO, TRANS
       DOUBLE COMPLEX AP(*), TAU(*), C(LDC,*), WORK(*)
       INTEGER*8 M, N, LDC, INFO




   F95 INTERFACE
       SUBROUTINE UPMTR(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
              WORK, INFO)

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

       SUBROUTINE UPMTR_64(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC,
              WORK, INFO)

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




   C INTERFACE
       #include <sunperf.h>

       void zupmtr(char side, char uplo, char trans, int m, int n,  doublecom-
                 plex  *ap, doublecomplex *tau, doublecomplex *c, int ldc, int
                 *info);

       void zupmtr_64(char side, char uplo, char trans, long m, long  n,  dou-
                 blecomplex  *ap,  doublecomplex  *tau, doublecomplex *c, long
                 ldc, long *info);



PURPOSE
       zupmtr 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 ZHPTRD using packed storage:

       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 triangular packed storage used in previous  call
                 to ZHPTRD;
                 =  'L': Lower triangular packed storage used in previous call
                 to ZHPTRD.


       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.


       AP (input)
                 dimension
                 (M*(M+1)/2) if SIDE = 'L'
                 (N*(N+1)/2) if SIDE = 'R'
                 The  vectors  which  define  the  elementary  reflectors,  as
                 returned  by  ZHPTRD.   AP  is  modified  by  the routine but
                 restored on exit.


       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 ZHPTRD.


       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
                 (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                        zupmtr(3P)