sormbr - VECT = 'Q', SORMBR overwrites the general real M-by-N matrix C with SIDE = 'L' SIDE = 'R' TRANS = 'N'
SUBROUTINE SORMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, * WORK, LWORK, INFO) CHARACTER * 1 VECT, SIDE, TRANS INTEGER M, N, K, LDA, LDC, LWORK, INFO REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE SORMBR_64( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, * LDC, WORK, LWORK, INFO) CHARACTER * 1 VECT, SIDE, TRANS INTEGER*8 M, N, K, LDA, LDC, LWORK, INFO REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE ORMBR( VECT, SIDE, [TRANS], [M], [N], K, A, [LDA], TAU, * C, [LDC], [WORK], [LWORK], [INFO]) CHARACTER(LEN=1) :: VECT, SIDE, TRANS INTEGER :: M, N, K, LDA, LDC, LWORK, INFO REAL, DIMENSION(:) :: TAU, WORK REAL, DIMENSION(:,:) :: A, C
SUBROUTINE ORMBR_64( VECT, SIDE, [TRANS], [M], [N], K, A, [LDA], * TAU, C, [LDC], [WORK], [LWORK], [INFO]) CHARACTER(LEN=1) :: VECT, SIDE, TRANS INTEGER(8) :: M, N, K, LDA, LDC, LWORK, INFO REAL, DIMENSION(:) :: TAU, WORK REAL, DIMENSION(:,:) :: A, C
#include <sunperf.h>
void sormbr(char vect, char side, char trans, int m, int n, int k, float *a, int lda, float *tau, float *c, int ldc, int *info);
void sormbr_64(char vect, char side, char trans, long m, long n, long k, float *a, long lda, float *tau, float *c, long ldc, long *info);
sormbr VECT = 'Q', SORMBR 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
If VECT = 'P', SORMBR overwrites the general real M-by-N matrix C with
SIDE = 'L' SIDE = 'R'
TRANS = 'N': P * C C * P
TRANS = 'T': P**T * C C * P**T
Here Q and P**T are the orthogonal matrices determined by SGEBRD when
reducing a real matrix A to bidiagonal form: A = Q * B * P**T. Q and
P**T are defined as products of elementary reflectors H(i)
and G(i)
respectively.
Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the order of the orthogonal matrix Q or P**T that is applied.
If VECT = 'Q', A is assumed to have been an NQ-by-K matrix:
if nq >= k, Q = H(1)
H(2)
. . . H(k);
if nq < k, Q = H(1)
H(2)
. . . H(nq-1).
If VECT = 'P', A is assumed to have been a K-by-NQ matrix:
if k < nq, P = G(1)
G(2)
. . . G(k);
if k >= nq, P = G(1)
G(2)
. . . G(nq-1).
= 'Q': apply Q or Q**T;
= 'P': apply P or P**T.
= 'L': apply Q, Q**T, P or P**T from the Left;
= 'R': apply Q, Q**T, P or P**T from the Right.
= 'N': No transpose, apply Q or P;
= 'T': Transpose, apply Q**T or P**T.
H(i)
and
G(i), whose products determine the matrices Q and P, as
returned by SGEBRD.
TAU(i)
must contain the scalar factor of the elementary
reflector H(i)
or G(i)
which determines Q or P, as returned
by SGEBRD in the array argument TAUQ or TAUP.
WORK(1)
returns the optimal LWORK.
If LWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the WORK array, returns this value as the first entry of the WORK array, and no error message related to LWORK is issued by XERBLA.
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value