Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgeqp3 (3p)

Name

cgeqp3 - compute a QR factorization with column pivoting of a matrix A

Synopsis

SUBROUTINE CGEQP3(M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK, INFO)

COMPLEX A(LDA,*), TAU(*), WORK(*)
INTEGER M, N, LDA, LWORK, INFO
INTEGER JPVT(*)
REAL RWORK(*)

SUBROUTINE CGEQP3_64(M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK,
INFO)

COMPLEX A(LDA,*), TAU(*), WORK(*)
INTEGER*8 M, N, LDA, LWORK, INFO
INTEGER*8 JPVT(*)
REAL RWORK(*)




F95 INTERFACE
SUBROUTINE GEQP3(M, N, A, LDA, JPVT, TAU, WORK, LWORK,
RWORK, INFO)

COMPLEX, DIMENSION(:) :: TAU, WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER :: M, N, LDA, LWORK, INFO
INTEGER, DIMENSION(:) :: JPVT
REAL, DIMENSION(:) :: RWORK

SUBROUTINE GEQP3_64(M, N, A, LDA, JPVT, TAU, WORK, LWORK,
RWORK, INFO)

COMPLEX, DIMENSION(:) :: TAU, WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER(8) :: M, N, LDA, LWORK, INFO
INTEGER(8), DIMENSION(:) :: JPVT
REAL, DIMENSION(:) :: RWORK




C INTERFACE
#include <sunperf.h>

void cgeqp3(int m, int n, complex *a, int lda, int *jpvt, complex *tau,
int *info);

void cgeqp3_64(long m, long n, complex *a, long lda, long  *jpvt,  com-
plex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           cgeqp3(3P)



NAME
       cgeqp3 - compute a QR factorization with column pivoting of a matrix A


SYNOPSIS
       SUBROUTINE CGEQP3(M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK, INFO)

       COMPLEX A(LDA,*), TAU(*), WORK(*)
       INTEGER M, N, LDA, LWORK, INFO
       INTEGER JPVT(*)
       REAL RWORK(*)

       SUBROUTINE CGEQP3_64(M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK,
             INFO)

       COMPLEX A(LDA,*), TAU(*), WORK(*)
       INTEGER*8 M, N, LDA, LWORK, INFO
       INTEGER*8 JPVT(*)
       REAL RWORK(*)




   F95 INTERFACE
       SUBROUTINE GEQP3(M, N, A, LDA, JPVT, TAU, WORK, LWORK,
              RWORK, INFO)

       COMPLEX, DIMENSION(:) :: TAU, WORK
       COMPLEX, DIMENSION(:,:) :: A
       INTEGER :: M, N, LDA, LWORK, INFO
       INTEGER, DIMENSION(:) :: JPVT
       REAL, DIMENSION(:) :: RWORK

       SUBROUTINE GEQP3_64(M, N, A, LDA, JPVT, TAU, WORK, LWORK,
              RWORK, INFO)

       COMPLEX, DIMENSION(:) :: TAU, WORK
       COMPLEX, DIMENSION(:,:) :: A
       INTEGER(8) :: M, N, LDA, LWORK, INFO
       INTEGER(8), DIMENSION(:) :: JPVT
       REAL, DIMENSION(:) :: RWORK




   C INTERFACE
       #include <sunperf.h>

       void cgeqp3(int m, int n, complex *a, int lda, int *jpvt, complex *tau,
                 int *info);

       void cgeqp3_64(long m, long n, complex *a, long lda, long  *jpvt,  com-
                 plex *tau, long *info);



PURPOSE
       cgeqp3  computes a QR factorization with column pivoting of a matrix A:
       A*P = Q*R  using Level 3 BLAS.


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 trapezoidal
                 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).


       JPVT (input/output)
                 On entry, if JPVT(J).ne.0, the J-th column of A  is  permuted
                 to  the front of A*P (a leading column); if 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.


       TAU (output)
                 The scalar factors of the elementary reflectors.


       WORK (workspace)
                 On exit, if INFO=0, WORK(1) returns the optimal LWORK.


       LWORK (input)
                 The  dimension  of the array WORK. LWORK >= N+1.  For optimal
                 performance LWORK >= ( N+1 )*NB,  where  NB  is  the  optimal
                 blocksize.

                 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.


       RWORK (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(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




                                  7 Nov 2015                        cgeqp3(3P)