sormrz - overwrite the general real M-by-N matrix C with SIDE = 'L' SIDE = 'R' TRANS = 'N'
SUBROUTINE SORMRZ( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC, * WORK, LWORK, INFO) CHARACTER * 1 SIDE, TRANS INTEGER M, N, K, L, LDA, LDC, LWORK, INFO REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE SORMRZ_64( SIDE, TRANS, M, N, K, L, A, LDA, TAU, C, LDC, * WORK, LWORK, INFO) CHARACTER * 1 SIDE, TRANS INTEGER*8 M, N, K, L, LDA, LDC, LWORK, INFO REAL A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE ORMRZ( SIDE, TRANS, [M], [N], K, L, A, [LDA], TAU, C, * [LDC], [WORK], [LWORK], [INFO]) CHARACTER(LEN=1) :: SIDE, TRANS INTEGER :: M, N, K, L, LDA, LDC, LWORK, INFO REAL, DIMENSION(:) :: TAU, WORK REAL, DIMENSION(:,:) :: A, C
SUBROUTINE ORMRZ_64( SIDE, TRANS, [M], [N], K, L, A, [LDA], TAU, C, * [LDC], [WORK], [LWORK], [INFO]) CHARACTER(LEN=1) :: SIDE, TRANS INTEGER(8) :: M, N, K, L, LDA, LDC, LWORK, INFO REAL, DIMENSION(:) :: TAU, WORK REAL, DIMENSION(:,:) :: A, C
#include <sunperf.h>
void sormrz(char side, char trans, int m, int n, int k, int l, float *a, int lda, float *tau, float *c, int ldc, int *info);
void sormrz_64(char side, char trans, long m, long n, long k, long l, float *a, long lda, float *tau, float *c, long ldc, long *info);
sormrz overwrites the general real M-by-N matrix C with TRANS = 'T': Q**T * C C * Q**T
where Q is a real orthogonal matrix defined as the product of k elementary reflectors
Q = H(1) H(2) . . . H(k)
as returned by STZRZF. Q is of order M if SIDE = 'L' and of order N if SIDE = 'R'.
= 'L': apply Q or Q**T from the Left;
= 'R': apply Q or Q**T from the Right.
= 'N': No transpose, apply Q;
= 'T': Transpose, apply Q**T.
TAU(i)
must contain the scalar factor of the elementary
reflector H(i), as returned by STZRZF.
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
Based on contributions by
A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA