dgelqf - compute an LQ factorization of a real M-by-N matrix A
SUBROUTINE DGELQF( M, N, A, LDA, TAU, WORK, LDWORK, INFO) INTEGER M, N, LDA, LDWORK, INFO DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
SUBROUTINE DGELQF_64( M, N, A, LDA, TAU, WORK, LDWORK, INFO) INTEGER*8 M, N, LDA, LDWORK, INFO DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
SUBROUTINE GELQF( [M], [N], A, [LDA], TAU, [WORK], [LDWORK], [INFO]) INTEGER :: M, N, LDA, LDWORK, INFO REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A
SUBROUTINE GELQF_64( [M], [N], A, [LDA], TAU, [WORK], [LDWORK], * [INFO]) INTEGER(8) :: M, N, LDA, LDWORK, INFO REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A
#include <sunperf.h>
void dgelqf(int m, int n, double *a, int lda, double *tau, int *info);
void dgelqf_64(long m, long n, double *a, long lda, double *tau, long *info);
dgelqf computes an LQ factorization of a real M-by-N matrix A: A = L * Q.
WORK(1)
returns the optimal LDWORK.
If LDWORK = -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 LDWORK is issued by XERBLA.
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value
The matrix Q is represented as a product of elementary reflectors
Q = H(k) . . . H(2) H(1), where k = min(m,n).
Each H(i)
has the form
H(i) = I - tau * v * v'
where tau is a real scalar, and v is a real vector with
v(1:i-1)
= 0 and v(i)
= 1; v(i+1:n)
is stored on exit in A(i,i+1:n),
and tau in TAU(i).