dgeqp3 - compute a QR factorization with column pivoting of a matrix A
SUBROUTINE DGEQP3( M, N, A, LDA, JPVT, TAU, WORK, LWORK, INFO) INTEGER M, N, LDA, LWORK, INFO INTEGER JPVT(*) DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
SUBROUTINE DGEQP3_64( M, N, A, LDA, JPVT, TAU, WORK, LWORK, INFO) INTEGER*8 M, N, LDA, LWORK, INFO INTEGER*8 JPVT(*) DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
SUBROUTINE GEQP3( [M], [N], A, [LDA], JPVT, TAU, [WORK], [LWORK], * [INFO]) INTEGER :: M, N, LDA, LWORK, INFO INTEGER, DIMENSION(:) :: JPVT REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A
SUBROUTINE GEQP3_64( [M], [N], A, [LDA], JPVT, TAU, [WORK], [LWORK], * [INFO]) INTEGER(8) :: M, N, LDA, LWORK, INFO INTEGER(8), DIMENSION(:) :: JPVT REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A
#include <sunperf.h>
void dgeqp3(int m, int n, double *a, int lda, int *jpvt, double *tau, int *info);
void dgeqp3_64(long m, long n, double *a, long lda, long *jpvt, double *tau, long *info);
dgeqp3 computes a QR factorization with column pivoting of a matrix A: A*P = Q*R using Level 3 BLAS.
min(M,N)
elementary
reflectors.
JPVT(J)
=0,
the J-th column of A is a free column.
On exit, if JPVT(J)
=K, then the J-th column of A*P was the
the K-th column of A.
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.
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 real/complex scalar, and v is a real/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).
Based on contributions by
G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain X. Sun, Computer Science Dept., Duke University, USA