cgeqpf - routine is deprecated and has been replaced by routine CGEQP3
SUBROUTINE CGEQPF(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO) COMPLEX A(LDA,*), TAU(*), WORK(*) INTEGER M, N, LDA, INFO INTEGER JPIVOT(*) REAL WORK2(*) SUBROUTINE CGEQPF_64(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO) COMPLEX A(LDA,*), TAU(*), WORK(*) INTEGER*8 M, N, LDA, INFO INTEGER*8 JPIVOT(*) REAL WORK2(*) F95 INTERFACE SUBROUTINE GEQPF(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO) COMPLEX, DIMENSION(:) :: TAU, WORK COMPLEX, DIMENSION(:,:) :: A INTEGER :: M, N, LDA, INFO INTEGER, DIMENSION(:) :: JPIVOT REAL, DIMENSION(:) :: WORK2 SUBROUTINE GEQPF_64(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO) COMPLEX, DIMENSION(:) :: TAU, WORK COMPLEX, DIMENSION(:,:) :: A INTEGER(8) :: M, N, LDA, INFO INTEGER(8), DIMENSION(:) :: JPIVOT REAL, DIMENSION(:) :: WORK2 C INTERFACE #include <sunperf.h> void cgeqpf(int m, int n, complex *a, int lda, int *jpivot, complex *tau, int *info); void cgeqpf_64(long m, long n, complex *a, long lda, long *jpivot, com- plex *tau, long *info);
Oracle Solaris Studio Performance Library cgeqpf(3P)
NAME
cgeqpf - routine is deprecated and has been replaced by routine CGEQP3
SYNOPSIS
SUBROUTINE CGEQPF(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO)
COMPLEX A(LDA,*), TAU(*), WORK(*)
INTEGER M, N, LDA, INFO
INTEGER JPIVOT(*)
REAL WORK2(*)
SUBROUTINE CGEQPF_64(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2, INFO)
COMPLEX A(LDA,*), TAU(*), WORK(*)
INTEGER*8 M, N, LDA, INFO
INTEGER*8 JPIVOT(*)
REAL WORK2(*)
F95 INTERFACE
SUBROUTINE GEQPF(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2,
INFO)
COMPLEX, DIMENSION(:) :: TAU, WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER :: M, N, LDA, INFO
INTEGER, DIMENSION(:) :: JPIVOT
REAL, DIMENSION(:) :: WORK2
SUBROUTINE GEQPF_64(M, N, A, LDA, JPIVOT, TAU, WORK, WORK2,
INFO)
COMPLEX, DIMENSION(:) :: TAU, WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER(8) :: M, N, LDA, INFO
INTEGER(8), DIMENSION(:) :: JPIVOT
REAL, DIMENSION(:) :: WORK2
C INTERFACE
#include <sunperf.h>
void cgeqpf(int m, int n, complex *a, int lda, int *jpivot, complex
*tau, int *info);
void cgeqpf_64(long m, long n, complex *a, long lda, long *jpivot, com-
plex *tau, long *info);
PURPOSE
cgeqpf 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.
ARGUMENTS
M (input) The number of rows of the matrix A. M >= 0.
N (input) The number of columns of the matrix A. N >= 0
A (input/output)
On entry, the M-by-N matrix A. On exit, the upper triangle
of the array contains the min(M,N)-by-N upper triangular
matrix R; the elements below the diagonal, together with the
array TAU, represent the unitary matrix Q as a product of
min(m,n) elementary reflectors.
LDA (input)
The leading dimension of the array A. LDA >= max(1,M).
JPIVOT (input/output)
On entry, if JPIVOT(i) .ne. 0, the i-th column of A is per-
muted 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 col-
umn of A.
TAU (output)
The scalar factors of the elementary reflectors.
WORK (workspace)
dimension(N)
WORK2 (workspace)
dimension(2*N)
INFO (output)
= 0: successful exit
< 0: if INFO = -i, the i-th argument had an illegal value
FURTHER DETAILS
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.
7 Nov 2015 cgeqpf(3P)