Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zgeqpf (3p)

Name

zgeqpf - routine is deprecated and has been replaced by routine ZGEQP3

Synopsis

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(*)




F95 INTERFACE
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




C INTERFACE
#include <sunperf.h>

void  zgeqpf(int m, int n, doublecomplex *a, int lda, int *jpivot, dou-
blecomplex *tau, int *info);

void zgeqpf_64(long  m,  long  n,  doublecomplex  *a,  long  lda,  long
*jpivot, doublecomplex *tau, long *info);

Description

Oracle Solaris Studio Performance Library                           zgeqpf(3P)



NAME
       zgeqpf - routine is deprecated and has been replaced by routine ZGEQP3


SYNOPSIS
       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(*)




   F95 INTERFACE
       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




   C INTERFACE
       #include <sunperf.h>

       void  zgeqpf(int m, int n, doublecomplex *a, int lda, int *jpivot, dou-
                 blecomplex *tau, int *info);

       void zgeqpf_64(long  m,  long  n,  doublecomplex  *a,  long  lda,  long
                 *jpivot, doublecomplex *tau, long *info);



PURPOSE
       zgeqpf routine is deprecated and has been replaced by routine ZGEQP3.

       ZGEQPF 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                        zgeqpf(3P)