zgerq2 - computes the RQ factorization of a general rectangular matrix using an unblocked algorithm
SUBROUTINE ZGERQ2(M, N, A, LDA, TAU, WORK, INFO) INTEGER INFO, LDA, M, N DOUBLE COMPLEX A(LDA,*), TAU(*), WORK(*) SUBROUTINE ZGERQ2_64(M, N, A, LDA, TAU, WORK, INFO) INTEGER*8 INFO, LDA, M, N DOUBLE COMPLEX A(LDA,*), TAU(*), WORK(*) F95 INTERFACE SUBROUTINE GERQ2(M, N, A, LDA, TAU, WORK, INFO) INTEGER :: M, N, LDA, INFO COMPLEX(8), DIMENSION(:) :: TAU, WORK COMPLEX(8), DIMENSION(:,:) :: A SUBROUTINE GERQ2_64(M, N, A, LDA, TAU, WORK, INFO) INTEGER(8) :: M, N, LDA, INFO COMPLEX(8), DIMENSION(:) :: TAU, WORK COMPLEX(8), DIMENSION(:,:) :: A C INTERFACE #include <sunperf.h> void zgerq2 (int m, int n, doublecomplex *a, int lda, doublecomplex *tau, int *info); void zgerq2_64 (long m, long n, doublecomplex *a, long lda, doublecom- plex *tau, long *info);
Oracle Solaris Studio Performance Library zgerq2(3P)
NAME
zgerq2 - computes the RQ factorization of a general rectangular matrix
using an unblocked algorithm
SYNOPSIS
SUBROUTINE ZGERQ2(M, N, A, LDA, TAU, WORK, INFO)
INTEGER INFO, LDA, M, N
DOUBLE COMPLEX A(LDA,*), TAU(*), WORK(*)
SUBROUTINE ZGERQ2_64(M, N, A, LDA, TAU, WORK, INFO)
INTEGER*8 INFO, LDA, M, N
DOUBLE COMPLEX A(LDA,*), TAU(*), WORK(*)
F95 INTERFACE
SUBROUTINE GERQ2(M, N, A, LDA, TAU, WORK, INFO)
INTEGER :: M, N, LDA, INFO
COMPLEX(8), DIMENSION(:) :: TAU, WORK
COMPLEX(8), DIMENSION(:,:) :: A
SUBROUTINE GERQ2_64(M, N, A, LDA, TAU, WORK, INFO)
INTEGER(8) :: M, N, LDA, INFO
COMPLEX(8), DIMENSION(:) :: TAU, WORK
COMPLEX(8), DIMENSION(:,:) :: A
C INTERFACE
#include <sunperf.h>
void zgerq2 (int m, int n, doublecomplex *a, int lda, doublecomplex
*tau, int *info);
void zgerq2_64 (long m, long n, doublecomplex *a, long lda, doublecom-
plex *tau, long *info);
PURPOSE
zgerq2 computes an RQ factorization of a complex m by n matrix A: A = R
* Q.
ARGUMENTS
M (input)
M is INTEGER
The number of rows of the matrix A. M >= 0.
N (input)
N is INTEGER
The number of columns of the matrix A. N >= 0.
A (input/output)
A is COMPLEX*16 array, dimension (LDA,N)
On entry, the m by n matrix A.
On exit, if M <= N, the upper triangle of the subarray
A(1:M,N-M+1:N) contains the m by m upper triangular matrix R;
if M >= N, the elements on and above the (M-N)-th subdiagonal
contain the M by N upper trapezoidal matrix R; the remaining
elements, with the array TAU, represent the unitary matrix Q
as a product of elementary reflectors (see Further Details).
LDA (input)
LDA is INTEGER
The leading dimension of the array A. LDA >= max(1,M).
TAU (output)
TAU is COMPLEX*16 array, dimension (min(M,N))
The scalar factors of the elementary reflectors (see Further
Details).
WORK (output)
WORK is COMPLEX*16 array, dimension (M)
INFO (output)
INFO is INTEGER
= 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 H(2)**H . . . H(k)**H, where k = min(m,n).
Each H(i) has the form
H(i) = I - tau * v * v**H
where tau is a complex scalar, and v is a complex vector with
v(n-k+i+1:n) = 0 and v(n-k+i) = 1; conjg(v(1:n-k+i-1)) is stored on
exit in A(m-k+i,1:n-k+i-1), and tau in TAU(i).
7 Nov 2015 zgerq2(3P)