dormlq - overwrite the general real M-by-N matrix C with SIDE = 'L' SIDE = 'R' TRANS = 'N'
SUBROUTINE DORMLQ( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, * LWORK, INFO) CHARACTER * 1 SIDE, TRANS INTEGER M, N, K, LDA, LDC, LWORK, INFO DOUBLE PRECISION A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE DORMLQ_64( SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, * WORK, LWORK, INFO) CHARACTER * 1 SIDE, TRANS INTEGER*8 M, N, K, LDA, LDC, LWORK, INFO DOUBLE PRECISION A(LDA,*), TAU(*), C(LDC,*), WORK(*)
SUBROUTINE ORMLQ( SIDE, [TRANS], [M], [N], [K], A, [LDA], TAU, C, * [LDC], [WORK], [LWORK], [INFO]) CHARACTER(LEN=1) :: SIDE, TRANS INTEGER :: M, N, K, LDA, LDC, LWORK, INFO REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A, C
SUBROUTINE ORMLQ_64( SIDE, [TRANS], [M], [N], [K], A, [LDA], TAU, C, * [LDC], [WORK], [LWORK], [INFO]) CHARACTER(LEN=1) :: SIDE, TRANS INTEGER(8) :: M, N, K, LDA, LDC, LWORK, INFO REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A, C
#include <sunperf.h>
void dormlq(char side, char trans, int m, int n, int k, double *a, int lda, double *tau, double *c, int ldc, int *info);
void dormlq_64(char side, char trans, long m, long n, long k, double *a, long lda, double *tau, double *c, long ldc, long *info);
dormlq 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(k) . . . H(2) H(1)
as returned by SGELQF. 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 SGELQF.
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