1DGELS(1)              LAPACK driver routine (version 3.1)             DGELS(1)
2
3
4

NAME

6       DGELS - overdetermined or underdetermined real linear systems involving
7       an M-by-N matrix A, or its transpose, using a QR or LQ factorization of
8       A
9

SYNOPSIS

11       SUBROUTINE DGELS( TRANS,  M, N, NRHS, A, LDA, B, LDB, WORK, LWORK, INFO
12                         )
13
14           CHARACTER     TRANS
15
16           INTEGER       INFO, LDA, LDB, LWORK, M, N, NRHS
17
18           DOUBLE        PRECISION A( LDA, * ), B( LDB, * ), WORK( * )
19

PURPOSE

21       DGELS solves overdetermined  or  underdetermined  real  linear  systems
22       involving  an  M-by-N matrix A, or its transpose, using a QR or LQ fac‐
23       torization of A.  It is assumed that A has full rank.
24
25       The following options are provided:
26
27       1. If TRANS = 'N' and m >= n:  find the least squares solution of
28          an overdetermined system, i.e., solve the least squares problem
29                       minimize || B - A*X ||.
30
31       2. If TRANS = 'N' and m < n:  find the minimum norm solution of
32          an underdetermined system A * X = B.
33
34       3. If TRANS = 'T' and m >= n:  find the minimum norm solution of
35          an undetermined system A**T * X = B.
36
37       4. If TRANS = 'T' and m < n:  find the least squares solution of
38          an overdetermined system, i.e., solve the least squares problem
39                       minimize || B - A**T * X ||.
40
41       Several right hand side vectors b and solution vectors x can be handled
42       in a single call; they are stored as the columns of the M-by-NRHS right
43       hand side matrix B and the N-by-NRHS solution matrix X.
44
45

ARGUMENTS

47       TRANS   (input) CHARACTER*1
48               = 'N': the linear system involves A;
49               = 'T': the linear system involves A**T.
50
51       M       (input) INTEGER
52               The number of rows of the matrix A.  M >= 0.
53
54       N       (input) INTEGER
55               The number of columns of the matrix A.  N >= 0.
56
57       NRHS    (input) INTEGER
58               The number of right hand sides, i.e., the number of columns  of
59               the matrices B and X. NRHS >=0.
60
61       A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
62               On  entry, the M-by-N matrix A.  On exit, if M >= N, A is over‐
63               written by details of its QR factorization as returned by  DGE‐
64               QRF;  if  M <  N, A is overwritten by details of its LQ factor‐
65               ization as returned by DGELQF.
66
67       LDA     (input) INTEGER
68               The leading dimension of the array A.  LDA >= max(1,M).
69
70       B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
71               On entry, the matrix B  of  right  hand  side  vectors,  stored
72               columnwise;  B  is  M-by-NRHS  if  TRANS = 'N', or N-by-NRHS if
73               TRANS = 'T'.  On exit, if INFO = 0, B  is  overwritten  by  the
74               solution vectors, stored columnwise: if TRANS = 'N' and m >= n,
75               rows 1 to n of B contain the least  squares  solution  vectors;
76               the  residual sum of squares for the solution in each column is
77               given by the sum of squares of elements N+1 to M in  that  col‐
78               umn;  if  TRANS  =  'N' and m < n, rows 1 to N of B contain the
79               minimum norm solution vectors; if TRANS = 'T' and m >= n,  rows
80               1 to M of B contain the minimum norm solution vectors; if TRANS
81               = 'T' and m < n, rows 1 to M of B  contain  the  least  squares
82               solution  vectors; the residual sum of squares for the solution
83               in each column is given by the sum of squares of  elements  M+1
84               to N in that column.
85
86       LDB     (input) INTEGER
87               The leading dimension of the array B. LDB >= MAX(1,M,N).
88
89       WORK       (workspace/output)   DOUBLE   PRECISION   array,   dimension
90       (MAX(1,LWORK))
91               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
92
93       LWORK   (input) INTEGER
94               The dimension of the array WORK.  LWORK >= max( 1,  MN  +  max(
95               MN,  NRHS  ) ).  For optimal performance, LWORK >= max( 1, MN +
96               max( MN, NRHS )*NB ).  where MN = min(M,N) and NB is the  opti‐
97               mum block size.
98
99               If  LWORK  = -1, then a workspace query is assumed; the routine
100               only calculates the optimal size of  the  WORK  array,  returns
101               this  value  as the first entry of the WORK array, and no error
102               message related to LWORK is issued by XERBLA.
103
104       INFO    (output) INTEGER
105               = 0:  successful exit
106               < 0:  if INFO = -i, the i-th argument had an illegal value
107               > 0:  if INFO =  i, the i-th diagonal element of the triangular
108               factor  of  A  is  zero, so that A does not have full rank; the
109               least squares solution could not be computed.
110
111
112
113 LAPACK driver routine (version 3.N1o)vember 2006                        DGELS(1)
Impressum