stpmqrt - pentagonal" real block reflector H to a general real matrix C, which consists of two blocks
SUBROUTINE STPMQRT(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO) CHARACTER*1 SIDE, TRANS INTEGER INFO, K, LDV, LDA, LDB, M, N, L, NB, LDT REAL V(LDV,*), A(LDA,*), B(LDB,*), T(LDT,*), WORK(*) SUBROUTINE STPMQRT_64(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO) CHARACTER*1 SIDE, TRANS INTEGER*8 INFO, K, LDV, LDA, LDB, M, N, L, NB, LDT REAL V(LDV,*), A(LDA,*), B(LDB,*), T(LDT,*), WORK(*) F95 INTERFACE SUBROUTINE TPMQRT(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO) REAL, DIMENSION(:,:) :: V, T, A, B INTEGER :: M, N, K, L, NB, LDV, LDT, LDA, LDB, INFO CHARACTER(LEN=1) :: SIDE, TRANS REAL, DIMENSION(:) :: WORK SUBROUTINE TPMQRT_64(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA, B, LDB, WORK, INFO) REAL, DIMENSION(:,:) :: V, T, A, B INTEGER(8) :: M, N, K, L, NB, LDV, LDT, LDA, LDB, INFO CHARACTER(LEN=1) :: SIDE, TRANS REAL, DIMENSION(:) :: WORK C INTERFACE #include <sunperf.h> void stpmqrt (char side, char trans, int m, int n, int k, int l, int nb, float *v, int ldv, float *t, int ldt, float *a, int lda, float *b, int ldb, int *info); void stpmqrt_64 (char side, char trans, long m, long n, long k, long l, long nb, float *v, long ldv, float *t, long ldt, float *a, long lda, float *b, long ldb, long *info);
Oracle Solaris Studio Performance Library stpmqrt(3P)
NAME
stpmqrt - apply a real orthogonal matrix Q obtained from a "triangular-
pentagonal" real block reflector H to a general real matrix C, which
consists of two blocks
SYNOPSIS
SUBROUTINE STPMQRT(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA,
B, LDB, WORK, INFO)
CHARACTER*1 SIDE, TRANS
INTEGER INFO, K, LDV, LDA, LDB, M, N, L, NB, LDT
REAL V(LDV,*), A(LDA,*), B(LDB,*), T(LDT,*), WORK(*)
SUBROUTINE STPMQRT_64(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A,
LDA, B, LDB, WORK, INFO)
CHARACTER*1 SIDE, TRANS
INTEGER*8 INFO, K, LDV, LDA, LDB, M, N, L, NB, LDT
REAL V(LDV,*), A(LDA,*), B(LDB,*), T(LDT,*), WORK(*)
F95 INTERFACE
SUBROUTINE TPMQRT(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A, LDA,
B, LDB, WORK, INFO)
REAL, DIMENSION(:,:) :: V, T, A, B
INTEGER :: M, N, K, L, NB, LDV, LDT, LDA, LDB, INFO
CHARACTER(LEN=1) :: SIDE, TRANS
REAL, DIMENSION(:) :: WORK
SUBROUTINE TPMQRT_64(SIDE, TRANS, M, N, K, L, NB, V, LDV, T, LDT, A,
LDA, B, LDB, WORK, INFO)
REAL, DIMENSION(:,:) :: V, T, A, B
INTEGER(8) :: M, N, K, L, NB, LDV, LDT, LDA, LDB, INFO
CHARACTER(LEN=1) :: SIDE, TRANS
REAL, DIMENSION(:) :: WORK
C INTERFACE
#include <sunperf.h>
void stpmqrt (char side, char trans, int m, int n, int k, int l, int
nb, float *v, int ldv, float *t, int ldt, float *a, int lda,
float *b, int ldb, int *info);
void stpmqrt_64 (char side, char trans, long m, long n, long k, long l,
long nb, float *v, long ldv, float *t, long ldt, float *a,
long lda, float *b, long ldb, long *info);
PURPOSE
stpmqrt applies a real orthogonal matrix Q obtained from a "triangular-
pentagonal" real block reflector H to a general real matrix C, which
consists of two blocks A and B.
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 B. M >= 0.
N (input)
N is INTEGER
The number of columns of the matrix B. N >= 0.
K (input)
K is INTEGER
The number of elementary reflectors whose product defines the
matrix Q.
L (input)
L is INTEGER
The order of the trapezoidal part of V.
K >= L >= 0. See Further Details.
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
STPQRT.
V (input)
V is REAL 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
STPQRT in B. See Further Details.
LDV (input)
LDV is INTEGER
The leading dimension of the array V.
If SIDE = 'L', LDV >= max(1,M);
if SIDE = 'R', LDV >= max(1,N).
T (input)
T is REAL array, dimension (LDT,K)
The upper triangular factors of the block reflectors as
returned by STPQRT, stored as a NB-by-K matrix.
LDT (input)
LDT is INTEGER
The leading dimension of the array T.
LDT >= NB.
A (input/output)
A is REAL array, dimension
(LDA,N) if SIDE = 'L' or
(LDA,K) if SIDE = 'R'
On entry, the K-by-N or M-by-K matrix A.
On exit, A is overwritten by the corresponding block of Q*C
or Q**T*C or C*Q or C*Q**T. See Further Details.
LDA (input)
LDA is INTEGER
The leading dimension of the array A.
If SIDE = 'L', LDC >= max(1,K);
If SIDE = 'R', LDC >= max(1,M).
B (input/output)
B is REAL array, dimension (LDB,N)
On entry, the M-by-N matrix B.
On exit, B is overwritten by the corresponding block of Q*C
or Q**T*C or C*Q or C*Q**T. See Further Details.
LDB (input)
LDB is INTEGER
The leading dimension of the array B.
LDB >= 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
FURTHER DETAILS
The columns of the pentagonal matrix V contain the elementary reflec-
tors H(1), H(2), ..., H(K); V is composed of a rectangular block V1 and
a trapezoidal block V2:
V = [V1]
[V2].
The size of the trapezoidal block V2 is determined by the parameter L,
where 0 <= L <= K; V2 is upper trapezoidal, consisting of the first L
rows of a K-by-K upper triangular matrix. If L=K, V2 is upper triangu-
lar; if L=0, there is no trapezoidal block, hence V = V1 is rectangu-
lar.
If SIDE = 'L': C = [A] where A is K-by-N, B is M-by-N and V is M-by-K.
[B]
If SIDE = 'R': C = [A B] where A is M-by-K, B is M-by-N and V is N-by-
K.
The real orthogonal matrix Q is formed from V and T.
If TRANS='N' and SIDE='L', C is on exit replaced with Q*C.
If TRANS='T' and SIDE='L', C is on exit replaced with Q**T*C.
If TRANS='N' and SIDE='R', C is on exit replaced with C*Q.
If TRANS='T' and SIDE='R', C is on exit replaced with C*Q**T.
7 Nov 2015 stpmqrt(3P)