Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sgemqrt (3p)

Name

sgemqrt - N matrix C with Q C, C Q, Q**T C, or C Q**T depe nding on values of SIDE and TRANS

Synopsis

SUBROUTINE SGEMQRT( SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT,  C,  LDC,
WORK, INFO )


CHARACTER*1 SIDE, TRANS

INTEGER INFO, K, LDV, LDC, M, N, NB, LDT

REAL V(LDV,*), C(LDC,*), T(LDT,*), WORK(*)


SUBROUTINE  SGEMQRT_64(  SIDE,  TRANS, M, N, K, NB, V, LDV, T, LDT,  C,
LDC, WORK, INFO )


CHARACTER*1 SIDE, TRANS

INTEGER*8 INFO, K, LDV, LDC, M, N, NB, LDT

REAL V(LDV,*), C(LDC,*), T(LDT,*), WORK(*)


F95 INTERFACE
SUBROUTINE GEMQRT( SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT,   C,  LDC,
WORK, INFO )


REAL, DIMENSION(:,:) :: V, T, C

INTEGER :: M, N, K, NB, LDV, LDT, LDC, INFO

CHARACTER(LEN=1) :: SIDE, TRANS

REAL, DIMENSION(:) :: WORK


SUBROUTINE  GEMQRT_64(  SIDE,  TRANS,  M, N, K, NB, V, LDV, T, LDT,  C,
LDC, WORK, INFO )


REAL, DIMENSION(:,:) :: V, T, C

INTEGER(8) :: M, N, K, NB, LDV, LDT, LDC, INFO

CHARACTER(LEN=1) :: SIDE, TRANS

REAL, DIMENSION(:) :: WORK


C INTERFACE
#include <sunperf.h>

void sgemqrt (char side, char trans, int m, int n, int k, int nb, float
*v,  int  ldv,  float  *t,  int  ldt,  float *c, int ldc, int
*info);


void sgemqrt_64 (char side, char trans, long m, long n,  long  k,  long
nb,  float  *v,  long ldv, float *t, long ldt, float *c, long
ldc, long *info);

Description

Oracle Solaris Studio Performance Library                          sgemqrt(3P)



NAME
       sgemqrt  -  overwrites  the general real M-by-N matrix C with Q C, C Q,
       Q**T C, or C Q**T depe nding on values of SIDE and TRANS


SYNOPSIS
       SUBROUTINE SGEMQRT( SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT,  C,  LDC,
                 WORK, INFO )


       CHARACTER*1 SIDE, TRANS

       INTEGER INFO, K, LDV, LDC, M, N, NB, LDT

       REAL V(LDV,*), C(LDC,*), T(LDT,*), WORK(*)


       SUBROUTINE  SGEMQRT_64(  SIDE,  TRANS, M, N, K, NB, V, LDV, T, LDT,  C,
                 LDC, WORK, INFO )


       CHARACTER*1 SIDE, TRANS

       INTEGER*8 INFO, K, LDV, LDC, M, N, NB, LDT

       REAL V(LDV,*), C(LDC,*), T(LDT,*), WORK(*)


   F95 INTERFACE
       SUBROUTINE GEMQRT( SIDE, TRANS, M, N, K, NB, V, LDV, T, LDT,   C,  LDC,
                 WORK, INFO )


       REAL, DIMENSION(:,:) :: V, T, C

       INTEGER :: M, N, K, NB, LDV, LDT, LDC, INFO

       CHARACTER(LEN=1) :: SIDE, TRANS

       REAL, DIMENSION(:) :: WORK


       SUBROUTINE  GEMQRT_64(  SIDE,  TRANS,  M, N, K, NB, V, LDV, T, LDT,  C,
                 LDC, WORK, INFO )


       REAL, DIMENSION(:,:) :: V, T, C

       INTEGER(8) :: M, N, K, NB, LDV, LDT, LDC, INFO

       CHARACTER(LEN=1) :: SIDE, TRANS

       REAL, DIMENSION(:) :: WORK


   C INTERFACE
       #include <sunperf.h>

       void sgemqrt (char side, char trans, int m, int n, int k, int nb, float
                 *v,  int  ldv,  float  *t,  int  ldt,  float *c, int ldc, int
                 *info);


       void sgemqrt_64 (char side, char trans, long m, long n,  long  k,  long
                 nb,  float  *v,  long ldv, float *t, long ldt, float *c, long
                 ldc, long *info);


PURPOSE
       sgemqrt overwrites the general real M-by-N matrix C with

       SIDE = 'L'     SIDE = 'R' TRANS = 'N':      Q C            C Q TRANS  =
       'T':   Q**T C            C Q**T

       where Q is a real orthogonal matrix defined as the product of K elemen-
       tary reflectors:

       Q = H(1) H(2) . . . H(K) = I - V T V**T

       generated using the compact WY representation as returned by SGEQRT.

       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**T from the Left;
                 = 'R': apply Q or Q**T from the Right.


       TRANS (input)
                 TRANS is CHARACTER*1
                 = 'N':  No transpose, apply Q;
                 = 'T':  Transpose, apply Q**T.


       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.


       NB (input)
                 NB is INTEGER
                 The block size used for the storage of T.  K >= NB >= 1.
                 This must be the same value of NB used to generate T
                 in CGEQRT.


       V (input)
                 V is REAL array, dimension (LDV,K)
                 The i-th column must contain the vector which defines the
                 elementary reflector H(i), for i = 1,2,...,k, as returned by
                 CGEQRT in the first K columns of its array argument A.


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


       T (input)
                 T is REAL array, dimension (LDT,K)
                 The upper triangular factors of the block reflectors
                 as returned by CGEQRT, stored as a NB-by-N matrix.


       LDT (input)
                 LDT is INTEGER
                 The leading dimension of the array T.  LDT >= NB.


       C (input/output)
                 C is REAL array, dimension (LDC,N)
                 On entry, the M-by-N matrix C.
                 On exit, C is overwritten by Q C, Q**T C, C Q**T or C Q.


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


       WORK (output)
                 WORK is REAL array. The dimension of WORK is
                 N*NB if SIDE = 'L', or  M*NB 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                       sgemqrt(3P)