dgeqrf - N matrix A
SUBROUTINE DGEQRF(M, N, A, LDA, TAU, WORK, LDWORK, INFO) INTEGER M, N, LDA, LDWORK, INFO DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*) SUBROUTINE DGEQRF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO) INTEGER*8 M, N, LDA, LDWORK, INFO DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*) F95 INTERFACE SUBROUTINE GEQRF(M, N, A, LDA, TAU, WORK, LDWORK, INFO) INTEGER :: M, N, LDA, LDWORK, INFO REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A SUBROUTINE GEQRF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO) INTEGER(8) :: M, N, LDA, LDWORK, INFO REAL(8), DIMENSION(:) :: TAU, WORK REAL(8), DIMENSION(:,:) :: A C INTERFACE #include <sunperf.h> void dgeqrf(int m, int n, double *a, int lda, double *tau, int *info); void dgeqrf_64(long m, long n, double *a, long lda, double *tau, long *info);
Oracle Solaris Studio Performance Library dgeqrf(3P)
NAME
dgeqrf - compute a QR factorization of a real M-by-N matrix A
SYNOPSIS
SUBROUTINE DGEQRF(M, N, A, LDA, TAU, WORK, LDWORK, INFO)
INTEGER M, N, LDA, LDWORK, INFO
DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
SUBROUTINE DGEQRF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO)
INTEGER*8 M, N, LDA, LDWORK, INFO
DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
F95 INTERFACE
SUBROUTINE GEQRF(M, N, A, LDA, TAU, WORK, LDWORK, INFO)
INTEGER :: M, N, LDA, LDWORK, INFO
REAL(8), DIMENSION(:) :: TAU, WORK
REAL(8), DIMENSION(:,:) :: A
SUBROUTINE GEQRF_64(M, N, A, LDA, TAU, WORK, LDWORK, INFO)
INTEGER(8) :: M, N, LDA, LDWORK, INFO
REAL(8), DIMENSION(:) :: TAU, WORK
REAL(8), DIMENSION(:,:) :: A
C INTERFACE
#include <sunperf.h>
void dgeqrf(int m, int n, double *a, int lda, double *tau, int *info);
void dgeqrf_64(long m, long n, double *a, long lda, double *tau, long
*info);
PURPOSE
dgeqrf computes a QR factorization of a real M-by-N matrix A: A = 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 elements on and
above the diagonal of the array contain the min(M,N)-by-N
upper trapezoidal matrix R (R is upper triangular if m >= n);
the elements below the diagonal, with the array TAU, repre-
sent the orthogonal matrix Q as a product of min(m,n) elemen-
tary reflectors (see Further Details).
LDA (input)
The leading dimension of the array A. LDA >= max(1,M).
TAU (output)
The scalar factors of the elementary reflectors (see Further
Details).
WORK (workspace)
On exit, if INFO = 0, WORK(1) returns the optimal LDWORK.
LDWORK (input)
The dimension of the array WORK. LDWORK >= max(1,N). For
optimum performance LDWORK >= N*NB, where NB is the optimal
blocksize.
If LDWORK = -1, then a workspace query is assumed; the rou-
tine 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 LDWORK is issued by XERBLA.
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 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),
and tau in TAU(i).
7 Nov 2015 dgeqrf(3P)