cgeqrf - compute a QR factorization of a complex M-by-N matrix A
SUBROUTINE CGEQRF( M, N, A, LDA, TAU, WORK, LDWORK, INFO) COMPLEX A(LDA,*), TAU(*), WORK(*) INTEGER M, N, LDA, LDWORK, INFO
SUBROUTINE CGEQRF_64( M, N, A, LDA, TAU, WORK, LDWORK, INFO) COMPLEX A(LDA,*), TAU(*), WORK(*) INTEGER*8 M, N, LDA, LDWORK, INFO
SUBROUTINE GEQRF( [M], [N], A, [LDA], TAU, [WORK], [LDWORK], [INFO]) COMPLEX, DIMENSION(:) :: TAU, WORK COMPLEX, DIMENSION(:,:) :: A INTEGER :: M, N, LDA, LDWORK, INFO
SUBROUTINE GEQRF_64( [M], [N], A, [LDA], TAU, [WORK], [LDWORK], * [INFO]) COMPLEX, DIMENSION(:) :: TAU, WORK COMPLEX, DIMENSION(:,:) :: A INTEGER(8) :: M, N, LDA, LDWORK, INFO
#include <sunperf.h>
void cgeqrf(int m, int n, complex *a, int lda, complex *tau, int *info);
void cgeqrf_64(long m, long n, complex *a, long lda, complex *tau, long *info);
cgeqrf computes a QR factorization of a complex M-by-N matrix A: A = Q * R.
min(m,n)
elementary reflectors (see Further
Details).
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(1) H(2) . . . H(k), where k = min(m,n).
Each H(i)
has the form
H(i) = I - tau * v * v'
where tau is a complex scalar, and v is a complex vector with
v(1:i-1)
= 0 and v(i)
= 1; v(i+1:m)
is stored on exit in A(i+1:m,i),
and tau in TAU(i).