--- rpl/lapack/lapack/dgelsd.f 2010/01/26 15:22:46 1.1 +++ rpl/lapack/lapack/dgelsd.f 2012/08/22 09:48:13 1.11 @@ -1,10 +1,218 @@ +*> \brief DGELSD computes the minimum-norm solution to a linear least squares problem for GE matrices +* +* =========== DOCUMENTATION =========== +* +* Online html documentation available at +* http://www.netlib.org/lapack/explore-html/ +* +*> \htmlonly +*> Download DGELSD + dependencies +*> +*> [TGZ] +*> +*> [ZIP] +*> +*> [TXT] +*> \endhtmlonly +* +* Definition: +* =========== +* +* SUBROUTINE DGELSD( M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, +* WORK, LWORK, IWORK, INFO ) +* +* .. Scalar Arguments .. +* INTEGER INFO, LDA, LDB, LWORK, M, N, NRHS, RANK +* DOUBLE PRECISION RCOND +* .. +* .. Array Arguments .. +* INTEGER IWORK( * ) +* DOUBLE PRECISION A( LDA, * ), B( LDB, * ), S( * ), WORK( * ) +* .. +* +* +*> \par Purpose: +* ============= +*> +*> \verbatim +*> +*> DGELSD computes the minimum-norm solution to a real linear least +*> squares problem: +*> minimize 2-norm(| b - A*x |) +*> using the singular value decomposition (SVD) of A. A is an M-by-N +*> matrix which may be rank-deficient. +*> +*> 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. +*> +*> The problem is solved in three steps: +*> (1) Reduce the coefficient matrix A to bidiagonal form with +*> Householder transformations, reducing the original problem +*> into a "bidiagonal least squares problem" (BLS) +*> (2) Solve the BLS using a divide and conquer approach. +*> (3) Apply back all the Householder tranformations to solve +*> the original least squares problem. +*> +*> The effective rank of A is determined by treating as zero those +*> singular values which are less than RCOND times the largest singular +*> value. +*> +*> The divide and conquer algorithm makes very mild assumptions about +*> floating point arithmetic. It will work on machines with a guard +*> digit in add/subtract, or on those binary machines without guard +*> digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or +*> Cray-2. It could conceivably fail on hexadecimal or decimal machines +*> without guard digits, but we know of none. +*> \endverbatim +* +* Arguments: +* ========== +* +*> \param[in] M +*> \verbatim +*> M is INTEGER +*> The number of rows of A. M >= 0. +*> \endverbatim +*> +*> \param[in] N +*> \verbatim +*> N is INTEGER +*> The number of columns of 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] A +*> \verbatim +*> A is DOUBLE PRECISION array, dimension (LDA,N) +*> On entry, the M-by-N matrix A. +*> On exit, A has been destroyed. +*> \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 M-by-NRHS right hand side matrix B. +*> On exit, B is overwritten by the N-by-NRHS solution +*> matrix X. If m >= n and RANK = n, the residual +*> sum-of-squares for the solution in the i-th column is given +*> by the sum of squares of elements n+1:m in that column. +*> \endverbatim +*> +*> \param[in] LDB +*> \verbatim +*> LDB is INTEGER +*> The leading dimension of the array B. LDB >= max(1,max(M,N)). +*> \endverbatim +*> +*> \param[out] S +*> \verbatim +*> S is DOUBLE PRECISION array, dimension (min(M,N)) +*> The singular values of A in decreasing order. +*> The condition number of A in the 2-norm = S(1)/S(min(m,n)). +*> \endverbatim +*> +*> \param[in] RCOND +*> \verbatim +*> RCOND is DOUBLE PRECISION +*> RCOND is used to determine the effective rank of A. +*> Singular values S(i) <= RCOND*S(1) are treated as zero. +*> If RCOND < 0, machine precision is used instead. +*> \endverbatim +*> +*> \param[out] RANK +*> \verbatim +*> RANK is INTEGER +*> The effective rank of A, i.e., the number of singular values +*> which are greater than RCOND*S(1). +*> \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 must be at least 1. +*> The exact minimum amount of workspace needed depends on M, +*> N and NRHS. As long as LWORK is at least +*> 12*N + 2*N*SMLSIZ + 8*N*NLVL + N*NRHS + (SMLSIZ+1)**2, +*> if M is greater than or equal to N or +*> 12*M + 2*M*SMLSIZ + 8*M*NLVL + M*NRHS + (SMLSIZ+1)**2, +*> if M is less than N, the code will execute correctly. +*> SMLSIZ is returned by ILAENV and is equal to the maximum +*> size of the subproblems at the bottom of the computation +*> tree (usually about 25), and +*> NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 ) +*> For good performance, LWORK should generally be larger. +*> +*> 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] IWORK +*> \verbatim +*> IWORK is INTEGER array, dimension (MAX(1,LIWORK)) +*> LIWORK >= max(1, 3 * MINMN * NLVL + 11 * MINMN), +*> where MINMN = MIN( M,N ). +*> On exit, if INFO = 0, IWORK(1) returns the minimum LIWORK. +*> \endverbatim +*> +*> \param[out] INFO +*> \verbatim +*> INFO is INTEGER +*> = 0: successful exit +*> < 0: if INFO = -i, the i-th argument had an illegal value. +*> > 0: the algorithm for computing the SVD failed to converge; +*> if INFO = i, i off-diagonal elements of an intermediate +*> bidiagonal form did not converge to zero. +*> \endverbatim +* +* Authors: +* ======== +* +*> \author Univ. of Tennessee +*> \author Univ. of California Berkeley +*> \author Univ. of Colorado Denver +*> \author NAG Ltd. +* +*> \date November 2011 +* +*> \ingroup doubleGEsolve +* +*> \par Contributors: +* ================== +*> +*> Ming Gu and Ren-Cang Li, Computer Science Division, University of +*> California at Berkeley, USA \n +*> Osni Marques, LBNL/NERSC, USA \n +* +* ===================================================================== SUBROUTINE DGELSD( M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, $ WORK, LWORK, IWORK, INFO ) * -* -- LAPACK driver routine (version 3.2) -- +* -- LAPACK driver routine (version 3.4.0) -- * -- LAPACK is a software package provided by Univ. of Tennessee, -- * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- -* November 2006 +* November 2011 * * .. Scalar Arguments .. INTEGER INFO, LDA, LDB, LWORK, M, N, NRHS, RANK @@ -15,123 +223,6 @@ DOUBLE PRECISION A( LDA, * ), B( LDB, * ), S( * ), WORK( * ) * .. * -* Purpose -* ======= -* -* DGELSD computes the minimum-norm solution to a real linear least -* squares problem: -* minimize 2-norm(| b - A*x |) -* using the singular value decomposition (SVD) of A. A is an M-by-N -* matrix which may be rank-deficient. -* -* 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. -* -* The problem is solved in three steps: -* (1) Reduce the coefficient matrix A to bidiagonal form with -* Householder transformations, reducing the original problem -* into a "bidiagonal least squares problem" (BLS) -* (2) Solve the BLS using a divide and conquer approach. -* (3) Apply back all the Householder tranformations to solve -* the original least squares problem. -* -* The effective rank of A is determined by treating as zero those -* singular values which are less than RCOND times the largest singular -* value. -* -* The divide and conquer algorithm makes very mild assumptions about -* floating point arithmetic. It will work on machines with a guard -* digit in add/subtract, or on those binary machines without guard -* digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or -* Cray-2. It could conceivably fail on hexadecimal or decimal machines -* without guard digits, but we know of none. -* -* Arguments -* ========= -* -* M (input) INTEGER -* The number of rows of A. M >= 0. -* -* N (input) INTEGER -* The number of columns of 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) DOUBLE PRECISION array, dimension (LDA,N) -* On entry, the M-by-N matrix A. -* On exit, A has been destroyed. -* -* 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 M-by-NRHS right hand side matrix B. -* On exit, B is overwritten by the N-by-NRHS solution -* matrix X. If m >= n and RANK = n, the residual -* sum-of-squares for the solution in the i-th column is given -* by the sum of squares of elements n+1:m in that column. -* -* LDB (input) INTEGER -* The leading dimension of the array B. LDB >= max(1,max(M,N)). -* -* S (output) DOUBLE PRECISION array, dimension (min(M,N)) -* The singular values of A in decreasing order. -* The condition number of A in the 2-norm = S(1)/S(min(m,n)). -* -* RCOND (input) DOUBLE PRECISION -* RCOND is used to determine the effective rank of A. -* Singular values S(i) <= RCOND*S(1) are treated as zero. -* If RCOND < 0, machine precision is used instead. -* -* RANK (output) INTEGER -* The effective rank of A, i.e., the number of singular values -* which are greater than RCOND*S(1). -* -* 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 must be at least 1. -* The exact minimum amount of workspace needed depends on M, -* N and NRHS. As long as LWORK is at least -* 12*N + 2*N*SMLSIZ + 8*N*NLVL + N*NRHS + (SMLSIZ+1)**2, -* if M is greater than or equal to N or -* 12*M + 2*M*SMLSIZ + 8*M*NLVL + M*NRHS + (SMLSIZ+1)**2, -* if M is less than N, the code will execute correctly. -* SMLSIZ is returned by ILAENV and is equal to the maximum -* size of the subproblems at the bottom of the computation -* tree (usually about 25), and -* NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 ) -* For good performance, LWORK should generally be larger. -* -* 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. -* -* IWORK (workspace) INTEGER array, dimension (MAX(1,LIWORK)) -* LIWORK >= 3 * MINMN * NLVL + 11 * MINMN, -* where MINMN = MIN( M,N ). -* -* INFO (output) INTEGER -* = 0: successful exit -* < 0: if INFO = -i, the i-th argument had an illegal value. -* > 0: the algorithm for computing the SVD failed to converge; -* if INFO = i, i off-diagonal elements of an intermediate -* bidiagonal form did not converge to zero. -* -* Further Details -* =============== -* -* Based on contributions by -* Ming Gu and Ren-Cang Li, Computer Science Division, University of -* California at Berkeley, USA -* Osni Marques, LBNL/NERSC, USA -* * ===================================================================== * * .. Parameters .. @@ -141,8 +232,8 @@ * .. Local Scalars .. LOGICAL LQUERY INTEGER IASCL, IBSCL, IE, IL, ITAU, ITAUP, ITAUQ, - $ LDWORK, MAXMN, MAXWRK, MINMN, MINWRK, MM, - $ MNTHR, NLVL, NWORK, SMLSIZ, WLALSD + $ LDWORK, LIWORK, MAXMN, MAXWRK, MINMN, MINWRK, + $ MM, MNTHR, NLVL, NWORK, SMLSIZ, WLALSD DOUBLE PRECISION ANRM, BIGNUM, BNRM, EPS, SFMIN, SMLNUM * .. * .. External Subroutines .. @@ -188,12 +279,14 @@ * following subroutine, as returned by ILAENV.) * MINWRK = 1 + LIWORK = 1 MINMN = MAX( 1, MINMN ) NLVL = MAX( INT( LOG( DBLE( MINMN ) / DBLE( SMLSIZ+1 ) ) / $ LOG( TWO ) ) + 1, 0 ) * IF( INFO.EQ.0 ) THEN MAXWRK = 0 + LIWORK = 3*MINMN*NLVL + 11*MINMN MM = M IF( M.GE.N .AND. M.GE.MNTHR ) THEN * @@ -261,6 +354,8 @@ END IF MINWRK = MIN( MINWRK, MAXWRK ) WORK( 1 ) = MAXWRK + IWORK( 1 ) = LIWORK + IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN INFO = -12 END IF @@ -526,6 +621,7 @@ * 10 CONTINUE WORK( 1 ) = MAXWRK + IWORK( 1 ) = LIWORK RETURN * * End of DGELSD