dgeql2 - compute the QL factorization of a general rectangular matrix using an unblocked algorithm
SUBROUTINE DGEQL2(M, N, A, LDA, TAU, WORK, INFO) INTEGER INFO, LDA, M, N DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*) SUBROUTINE DGEQL2_64(M, N, A, LDA, TAU, WORK, INFO) INTEGER*8 INFO, LDA, M, N DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*) F95 INTERFACE SUBROUTINE GEQL2(M, N, A, LDA, TAU, WORK, INFO) INTEGER :: M, N, LDA, INFO REAL(8), DIMENSION(:,:) :: A REAL(8), DIMENSION(:) :: TAU, WORK SUBROUTINE GEQL2_64(M, N, A, LDA, TAU, WORK, INFO) INTEGER(8) :: M, N, LDA, INFO REAL(8), DIMENSION(:,:) :: A REAL(8), DIMENSION(:) :: TAU, WORK C INTERFACE #include <sunperf.h> void dgeql2 (int m, int n, double *a, int lda, double *tau, int *info); void dgeql2_64 (long m, long n, double *a, long lda, double *tau, long *info);
Oracle Solaris Studio Performance Library dgeql2(3P)
NAME
dgeql2 - compute the QL factorization of a general rectangular matrix
using an unblocked algorithm
SYNOPSIS
SUBROUTINE DGEQL2(M, N, A, LDA, TAU, WORK, INFO)
INTEGER INFO, LDA, M, N
DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
SUBROUTINE DGEQL2_64(M, N, A, LDA, TAU, WORK, INFO)
INTEGER*8 INFO, LDA, M, N
DOUBLE PRECISION A(LDA,*), TAU(*), WORK(*)
F95 INTERFACE
SUBROUTINE GEQL2(M, N, A, LDA, TAU, WORK, INFO)
INTEGER :: M, N, LDA, INFO
REAL(8), DIMENSION(:,:) :: A
REAL(8), DIMENSION(:) :: TAU, WORK
SUBROUTINE GEQL2_64(M, N, A, LDA, TAU, WORK, INFO)
INTEGER(8) :: M, N, LDA, INFO
REAL(8), DIMENSION(:,:) :: A
REAL(8), DIMENSION(:) :: TAU, WORK
C INTERFACE
#include <sunperf.h>
void dgeql2 (int m, int n, double *a, int lda, double *tau, int *info);
void dgeql2_64 (long m, long n, double *a, long lda, double *tau, long
*info);
PURPOSE
dgeql2 computes a QL factorization of a real m by n matrix A: A= Q*L.
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 DOUBLE PRECISION array, dimension (LDA,N)
On entry, the m by n matrix A.
On exit, if m >= n, the lower triangle of the subarray A(m-
n+1:m,1:n) contains the n by n lower triangular matrix L; if
m <= n, the elements on and below the (n-m)-th superdiagonal
contain the m by n lower trapezoidal matrix L; the remaining
elements, with the array TAU, represent the orthogonal 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 DOUBLE PRECISION array, dimension (min(M,N))
The scalar factors of the elementary reflectors (see Further
Details).
WORK (output)
WORK is DOUBLE PRECISION array, dimension (N)
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(k) . . . H(2) H(1), where k = min(m,n).
Each H(i) has the form
H(i) = I - tau * v * v**T
where tau is a complex scalar, and v is a complex vector with
v(m-k+i+1:m) = 0 and v(m-k+i) = 1; v(1:m-k+i-1) is stored on exit in
A(1:m-k+i-1,n-k+i), and tau in TAU(i).
7 Nov 2015 dgeql2(3P)