Diff for /rpl/lapack/lapack/dgels.f between versions 1.8 and 1.9

version 1.8, 2011/07/22 07:38:04 version 1.9, 2011/11/21 20:42:51
Line 1 Line 1
   *> \brief <b> DGELS solves overdetermined or underdetermined systems for GE matrices</b>
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *> \htmlonly
   *> Download DGELS + dependencies 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dgels.f"> 
   *> [TGZ]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dgels.f"> 
   *> [ZIP]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dgels.f"> 
   *> [TXT]</a>
   *> \endhtmlonly 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE DGELS( TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK,
   *                         INFO )
   * 
   *       .. Scalar Arguments ..
   *       CHARACTER          TRANS
   *       INTEGER            INFO, LDA, LDB, LWORK, M, N, NRHS
   *       ..
   *       .. Array Arguments ..
   *       DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), WORK( * )
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> DGELS solves overdetermined or underdetermined real linear systems
   *> involving an M-by-N matrix A, or its 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 = 'T' and m >= n:  find the minimum norm solution of
   *>    an undetermined system A**T * X = B.
   *>
   *> 4. If TRANS = 'T' and m < n:  find the least squares solution of
   *>    an overdetermined system, i.e., solve the least squares problem
   *>                 minimize || B - A**T * 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.
   *> \endverbatim
   *
   *  Arguments:
   *  ==========
   *
   *> \param[in] TRANS
   *> \verbatim
   *>          TRANS is CHARACTER*1
   *>          = 'N': the linear system involves A;
   *>          = 'T': the linear system involves A**T.
   *> \endverbatim
   *>
   *> \param[in] M
   *> \verbatim
   *>          M is INTEGER
   *>          The number of rows of the matrix A.  M >= 0.
   *> \endverbatim
   *>
   *> \param[in] N
   *> \verbatim
   *>          N is INTEGER
   *>          The number of columns of the matrix A.  N >= 0.
   *> \endverbatim
   *>
   *> \param[in] NRHS
   *> \verbatim
   *>          NRHS is INTEGER
   *>          The number of right hand sides, i.e., the number of
   *>          columns of the matrices B and X. NRHS >=0.
   *> \endverbatim
   *>
   *> \param[in,out] A
   *> \verbatim
   *>          A is DOUBLE PRECISION array, dimension (LDA,N)
   *>          On entry, the M-by-N matrix A.
   *>          On exit,
   *>            if M >= N, A is overwritten by details of its QR
   *>                       factorization as returned by DGEQRF;
   *>            if M <  N, A is overwritten by details of its LQ
   *>                       factorization as returned by DGELQF.
   *> \endverbatim
   *>
   *> \param[in] LDA
   *> \verbatim
   *>          LDA is INTEGER
   *>          The leading dimension of the array A.  LDA >= max(1,M).
   *> \endverbatim
   *>
   *> \param[in,out] B
   *> \verbatim
   *>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
   *>          On entry, the matrix B of right hand side vectors, stored
   *>          columnwise; B is M-by-NRHS if TRANS = 'N', or N-by-NRHS
   *>          if TRANS = 'T'.
   *>          On exit, if INFO = 0, B is overwritten by the solution
   *>          vectors, stored columnwise:
   *>          if TRANS = '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 TRANS = 'N' and m < n, rows 1 to N of B contain the
   *>          minimum norm solution vectors;
   *>          if TRANS = 'T' and m >= n, rows 1 to M of B contain the
   *>          minimum norm solution vectors;
   *>          if TRANS = 'T' 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.
   *> \endverbatim
   *>
   *> \param[in] LDB
   *> \verbatim
   *>          LDB is INTEGER
   *>          The leading dimension of the array B. LDB >= MAX(1,M,N).
   *> \endverbatim
   *>
   *> \param[out] WORK
   *> \verbatim
   *>          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
   *>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
   *> \endverbatim
   *>
   *> \param[in] LWORK
   *> \verbatim
   *>          LWORK is INTEGER
   *>          The dimension of the array WORK.
   *>          LWORK >= max( 1, MN + max( MN, NRHS ) ).
   *>          For optimal performance,
   *>          LWORK >= max( 1, MN + max( MN, NRHS )*NB ).
   *>          where MN = min(M,N) and NB is the optimum block size.
   *>
   *>          If LWORK = -1, then a workspace query is assumed; the routine
   *>          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 LWORK is issued by XERBLA.
   *> \endverbatim
   *>
   *> \param[out] INFO
   *> \verbatim
   *>          INFO is INTEGER
   *>          = 0:  successful exit
   *>          < 0:  if INFO = -i, the i-th argument had an illegal value
   *>          > 0:  if INFO =  i, the i-th diagonal element of the
   *>                triangular factor of A is zero, so that A does not have
   *>                full rank; the least squares solution could not be
   *>                computed.
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2011
   *
   *> \ingroup doubleGEsolve
   *
   *  =====================================================================
       SUBROUTINE DGELS( TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK,        SUBROUTINE DGELS( TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK,
      $                  INFO )       $                  INFO )
 *  *
 *  -- LAPACK driver routine (version 3.3.1) --  *  -- LAPACK driver routine (version 3.4.0) --
 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *  -- April 2011                                                      --  *     November 2011
 *  *
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       CHARACTER          TRANS        CHARACTER          TRANS
Line 14 Line 196
       DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), WORK( * )        DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), WORK( * )
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  DGELS solves overdetermined or underdetermined real linear systems  
 *  involving an M-by-N matrix A, or its 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 = 'T' and m >= n:  find the minimum norm solution of  
 *     an undetermined system A**T * X = B.  
 *  
 *  4. If TRANS = 'T' and m < n:  find the least squares solution of  
 *     an overdetermined system, i.e., solve the least squares problem  
 *                  minimize || B - A**T * 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  
 *  =========  
 *  
 *  TRANS   (input) CHARACTER*1  
 *          = 'N': the linear system involves A;  
 *          = 'T': the linear system involves A**T.  
 *  
 *  M       (input) INTEGER  
 *          The number of rows of the matrix A.  M >= 0.  
 *  
 *  N       (input) INTEGER  
 *          The number of columns of the matrix A.  N >= 0.  
 *  
 *  NRHS    (input) INTEGER  
 *          The number of right hand sides, i.e., the number of  
 *          columns of the matrices B and X. NRHS >=0.  
 *  
 *  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)  
 *          On entry, the M-by-N matrix A.  
 *          On exit,  
 *            if M >= N, A is overwritten by details of its QR  
 *                       factorization as returned by DGEQRF;  
 *            if M <  N, A is overwritten by details of its LQ  
 *                       factorization as returned by DGELQF.  
 *  
 *  LDA     (input) INTEGER  
 *          The leading dimension of the array A.  LDA >= max(1,M).  
 *  
 *  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)  
 *          On entry, the matrix B of right hand side vectors, stored  
 *          columnwise; B is M-by-NRHS if TRANS = 'N', or N-by-NRHS  
 *          if TRANS = 'T'.  
 *          On exit, if INFO = 0, B is overwritten by the solution  
 *          vectors, stored columnwise:  
 *          if TRANS = '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 TRANS = 'N' and m < n, rows 1 to N of B contain the  
 *          minimum norm solution vectors;  
 *          if TRANS = 'T' and m >= n, rows 1 to M of B contain the  
 *          minimum norm solution vectors;  
 *          if TRANS = 'T' 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) INTEGER  
 *          The leading dimension of the array B. LDB >= MAX(1,M,N).  
 *  
 *  WORK    (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))  
 *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.  
 *  
 *  LWORK   (input) INTEGER  
 *          The dimension of the array WORK.  
 *          LWORK >= max( 1, MN + max( MN, NRHS ) ).  
 *          For optimal performance,  
 *          LWORK >= max( 1, MN + max( MN, NRHS )*NB ).  
 *          where MN = min(M,N) and NB is the optimum block size.  
 *  
 *          If LWORK = -1, then a workspace query is assumed; the routine  
 *          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 LWORK is issued by XERBLA.  
 *  
 *  INFO    (output) INTEGER  
 *          = 0:  successful exit  
 *          < 0:  if INFO = -i, the i-th argument had an illegal value  
 *          > 0:  if INFO =  i, the i-th diagonal element of the  
 *                triangular factor of A is zero, so that A does not have  
 *                full rank; the least squares solution could not be  
 *                computed.  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. Parameters ..  *     .. Parameters ..

Removed from v.1.8  
changed lines
  Added in v.1.9


CVSweb interface <joel.bertrand@systella.fr>