Contents


NAME

     dgeqpf - routine is deprecated and has been replaced by rou-
     tine SGEQP3

SYNOPSIS

     SUBROUTINE DGEQPF(M, N, A, LDA, JPIVOT, TAU, WORK, INFO)

     INTEGER M, N, LDA, INFO
     INTEGER JPIVOT(*)
     DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)

     SUBROUTINE DGEQPF_64(M, N, A, LDA, JPIVOT, TAU, WORK, INFO)

     INTEGER*8 M, N, LDA, INFO
     INTEGER*8 JPIVOT(*)
     DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE GEQPF([M], [N], A, [LDA], JPIVOT, TAU, [WORK], [INFO])

     INTEGER :: M, N, LDA, INFO
     INTEGER, DIMENSION(:) :: JPIVOT
     REAL(8), DIMENSION(:) :: TAU, WORK
     REAL(8), DIMENSION(:,:) :: A

     SUBROUTINE GEQPF_64([M], [N], A, [LDA], JPIVOT, TAU, [WORK], [INFO])

     INTEGER(8) :: M, N, LDA, INFO
     INTEGER(8), DIMENSION(:) :: JPIVOT
     REAL(8), DIMENSION(:) :: TAU, WORK
     REAL(8), DIMENSION(:,:) :: A

  C INTERFACE
     #include <sunperf.h>

     void dgeqpf(int m, int n, double *a, int lda,  int  *jpivot,
               double *tau, int *info);

     void dgeqpf_64(long m, long n, double  *a,  long  lda,  long
               *jpivot, double *tau, long *info);

PURPOSE

     dgeqpf routine is deprecated and has been replaced  by  rou-
     tine SGEQP3.

     SGEQPF computes a QR factorization with column pivoting of a
     real 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 orthogonal 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  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.

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

     WORK (workspace)
               dimension(N)

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal 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 real scalar, and v is a real 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.