zgels - solve overdetermined or underdetermined complex linear systems involving an M-by-N matrix A, or its conjugate-transpose, using a QR or LQ factorization of A
SUBROUTINE ZGELS(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK, INFO) CHARACTER*1 TRANSA DOUBLE COMPLEX A(LDA,*), B(LDB,*), WORK(*) INTEGER M, N, NRHS, LDA, LDB, LDWORK, INFO SUBROUTINE ZGELS_64(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK, INFO) CHARACTER*1 TRANSA DOUBLE COMPLEX A(LDA,*), B(LDB,*), WORK(*) INTEGER*8 M, N, NRHS, LDA, LDB, LDWORK, INFO F95 INTERFACE SUBROUTINE GELS(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK, INFO) CHARACTER(LEN=1) :: TRANSA COMPLEX(8), DIMENSION(:) :: WORK COMPLEX(8), DIMENSION(:,:) :: A, B INTEGER :: M, N, NRHS, LDA, LDB, LDWORK, INFO SUBROUTINE GELS_64(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK, INFO) CHARACTER(LEN=1) :: TRANSA COMPLEX(8), DIMENSION(:) :: WORK COMPLEX(8), DIMENSION(:,:) :: A, B INTEGER(8) :: M, N, NRHS, LDA, LDB, LDWORK, INFO C INTERFACE #include <sunperf.h> void zgels (char transa, int m, int n, int nrhs, doublecomplex* a, int lda, doublecomplex* b, int ldb, int* info); void zgels_64 (char transa, long m, long n, long nrhs, doublecomplex* a, long lda, doublecomplex* b, long ldb, long* info);
Oracle Solaris Studio Performance Library zgels(3P)
NAME
zgels - solve overdetermined or underdetermined complex linear systems
involving an M-by-N matrix A, or its conjugate-transpose, using a QR or
LQ factorization of A
SYNOPSIS
SUBROUTINE ZGELS(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK,
INFO)
CHARACTER*1 TRANSA
DOUBLE COMPLEX A(LDA,*), B(LDB,*), WORK(*)
INTEGER M, N, NRHS, LDA, LDB, LDWORK, INFO
SUBROUTINE ZGELS_64(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK, LDWORK,
INFO)
CHARACTER*1 TRANSA
DOUBLE COMPLEX A(LDA,*), B(LDB,*), WORK(*)
INTEGER*8 M, N, NRHS, LDA, LDB, LDWORK, INFO
F95 INTERFACE
SUBROUTINE GELS(TRANSA, M, N, NRHS, A, LDA, B, LDB, WORK,
LDWORK, INFO)
CHARACTER(LEN=1) :: TRANSA
COMPLEX(8), DIMENSION(:) :: WORK
COMPLEX(8), DIMENSION(:,:) :: A, B
INTEGER :: M, N, NRHS, LDA, LDB, LDWORK, INFO
SUBROUTINE GELS_64(TRANSA, M, N, NRHS, A, LDA, B, LDB,
WORK, LDWORK, INFO)
CHARACTER(LEN=1) :: TRANSA
COMPLEX(8), DIMENSION(:) :: WORK
COMPLEX(8), DIMENSION(:,:) :: A, B
INTEGER(8) :: M, N, NRHS, LDA, LDB, LDWORK, INFO
C INTERFACE
#include <sunperf.h>
void zgels (char transa, int m, int n, int nrhs, doublecomplex* a, int
lda, doublecomplex* b, int ldb, int* info);
void zgels_64 (char transa, long m, long n, long nrhs, doublecomplex*
a, long lda, doublecomplex* b, long ldb, long* info);
PURPOSE
zgels solves overdetermined or underdetermined complex linear systems
involving an M-by-N matrix A, or its conjugate-transpose, using a QR or
LQ factorization of A. It is assumed that A has full rank.
The following options are provided:
1. If TRANS = 'N' and m >= n: find the least squares solution of an
overdetermined system, i.e., solve the least squares problem
minimize || B - A*X ||.
2. If TRANS = 'N' and m < n: find the minimum norm solution of an
underdetermined system A * X = B.
3. If TRANS = 'C' and m >= n: find the minimum norm solution of an
undetermined system A**H * X = B.
4. If TRANS = 'C' and m < n: find the least squares solution of an
overdetermined system, i.e., solve the least squares problem
minimize || B - A**H * X ||.
Several right hand side vectors b and solution vectors x can be handled
in a single call; they are stored as the columns of the M-by-NRHS right
hand side matrix B and the N-by-NRHS solution matrix X.
ARGUMENTS
TRANSA (input)
= 'N': the linear system involves A;
= 'C': the linear system involves A**H.
M (input) The number of rows of the matrix A. M >= 0.
N (input) The number of columns of the matrix A. N >= 0.
NRHS (input)
The number of right hand sides, i.e., the number of columns
of the matrices B and X. NRHS >= 0.
A (input/output)
On entry, the M-by-N matrix A.
if M >= N, A is overwritten by details of its QR factoriza-
tion as returned by ZGEQRF;
if M < N, A is overwritten by details of its LQ factoriza-
tion as returned by ZGELQF.
LDA (input)
The leading dimension of the array A.
LDA >= max(1,M).
B (input/output)
On entry, the matrix B of right hand side vectors, stored
columnwise; B is M-by-NRHS if TRANSA = 'N', or N-by-NRHS if
TRANSA = 'C'.
On exit, B is overwritten by the solution vectors, stored
columnwise:
if TRANSA = 'N' and m >= n, rows 1 to n of B contain the
least squares solution vectors; the residual sum of squares
for the solution in each column is given by the sum of
squares of elements N+1 to M in that column;
if TRANSA = 'N' and m < n, rows 1 to N of B contain the mini-
mum norm solution vectors;
if TRANSA = 'C' and m >= n, rows 1 to M of B contain the min-
imum norm solution vectors;
if TRANSA = 'C' and m < n, rows 1 to M of B contain the least
squares solution vectors; the residual sum of squares for the
solution in each column is given by the sum of squares of
elements M+1 to N in that column.
LDB (input)
The leading dimension of the array B.
LDB >= MAX(1,M,N).
WORK (workspace)
On exit, if INFO = 0, WORK(1) returns the optimal LDWORK.
LDWORK (input)
The dimension of the array WORK.
LDWORK >= max( 1, MN + max( MN, NRHS )). For optimal perfor-
mance,
LDWORK >= max( 1, MN + max( MN, NRHS )*NB ),
where MN = min(M,N) and NB is the optimum block size.
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.
7 Nov 2015 zgels(3P)