dormrz
dormrz - overwrite the general real M-by-N matrix C with SIDE = 'L' SIDE = 'R' TRANS = 'N'
SUBROUTINE DORMRZ( 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
DOUBLE PRECISION A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE DORMRZ_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
DOUBLE PRECISION 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(8), DIMENSION(:) :: TAU, WORK
REAL(8), 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(8), DIMENSION(:) :: TAU, WORK
REAL(8), DIMENSION(:,:) :: A, C
#include <sunperf.h>
void dormrz(char side, char trans, int m, int n, int k, int l, double *a, int lda, double *tau, double *c, int ldc, int *info);
void dormrz_64(char side, char trans, long m, long n, long k, long l, double *a, long lda, double *tau, double *c, long ldc, long *info);
dormrz 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'.
-
* SIDE (input)
-
-
* TRANS (input)
-
-
* M (input)
-
The number of rows of the matrix C. M >= 0.
-
* N (input)
-
The number of columns of the matrix C. N >= 0.
-
* K (input)
-
The number of elementary reflectors whose product defines
the matrix Q.
If SIDE = 'L', M >= K >= 0;
if SIDE = 'R', N >= K >= 0.
-
* L (input)
-
The number of columns of the matrix A containing
the meaningful part of the Householder reflectors.
If SIDE = 'L', M >= L >= 0, if SIDE = 'R', N >= L >= 0.
-
* A (input)
-
(LDA,M) if SIDE = 'L',
(LDA,N) if SIDE = 'R'
The i-th row must contain the vector which defines the
elementary reflector H(i), for i = 1,2,...,k, as returned by
STZRZF in the last k rows of its array argument A.
A is modified by the routine but restored on exit.
-
* LDA (input)
-
The leading dimension of the array A. LDA >= max(1,K).
-
* TAU (input)
-
TAU(i) must contain the scalar factor of the elementary
reflector H(i), as returned by STZRZF.
-
* C (input/output)
-
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)
-
On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
-
* LWORK (input)
-
The dimension of the array WORK.
If SIDE = 'L', LWORK >= max(1,N);
if SIDE = 'R', LWORK >= max(1,M).
For optimum performance LWORK >= N*NB if SIDE = 'L', and
LWORK >= M*NB if SIDE = 'R', where NB is the optimal
blocksize.
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.
-
* INFO (output)
-