zgeqpf - routine is deprecated and has been replaced by routine CGEQP3
SUBROUTINE ZGEQPF( M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO) DOUBLE COMPLEX A(LDA,*), TAU(*), WORK(*) INTEGER M, N, LDA, INFO INTEGER JPIVOT(*) DOUBLE PRECISION WORK2(*)
SUBROUTINE ZGEQPF_64( M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO) DOUBLE COMPLEX A(LDA,*), TAU(*), WORK(*) INTEGER*8 M, N, LDA, INFO INTEGER*8 JPIVOT(*) DOUBLE PRECISION WORK2(*)
SUBROUTINE GEQPF( [M], [N], A, [LDA], JPIVOT, TAU, [WORK], [WORK2], * [INFO]) COMPLEX(8), DIMENSION(:) :: TAU, WORK COMPLEX(8), DIMENSION(:,:) :: A INTEGER :: M, N, LDA, INFO INTEGER, DIMENSION(:) :: JPIVOT REAL(8), DIMENSION(:) :: WORK2
SUBROUTINE GEQPF_64( [M], [N], A, [LDA], JPIVOT, TAU, [WORK], [WORK2], * [INFO]) COMPLEX(8), DIMENSION(:) :: TAU, WORK COMPLEX(8), DIMENSION(:,:) :: A INTEGER(8) :: M, N, LDA, INFO INTEGER(8), DIMENSION(:) :: JPIVOT REAL(8), DIMENSION(:) :: WORK2
#include <sunperf.h>
void zgeqpf(int m, int n, doublecomplex *a, int lda, int *jpivot, doublecomplex *tau, int *info);
void zgeqpf_64(long m, long n, doublecomplex *a, long lda, long *jpivot, doublecomplex *tau, long *info);
zgeqpf routine is deprecated and has been replaced by routine CGEQP3.
CGEQPF computes a QR factorization with column pivoting of a complex M-by-N matrix A: A*P = Q*R.
min(m,n)
elementary reflectors.
JPIVOT(i)
.ne. 0, the i-th column of A is permuted
to the front of A*P (a leading column); if JPIVOT(i)
= 0,
the i-th column of A is a free column.
On exit, if JPIVOT(i)
= k, then the i-th column of A*P
was the k-th column of A.
dimension(N)
dimension(2*N)
= 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(n)
Each H(i)
has the form
H = 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).
The matrix P is represented in jpvt as follows: If
jpvt(j) = i
then the jth column of P is the ith canonical unit vector.