aboutsummaryrefslogtreecommitdiff
path: root/SRC/clalsd.f
diff options
context:
space:
mode:
authorjulie <julielangou@users.noreply.github.com>2011-10-06 06:53:11 +0000
committerjulie <julielangou@users.noreply.github.com>2011-10-06 06:53:11 +0000
commite1d39294aee16fa6db9ba079b14442358217db71 (patch)
tree30e5aa04c1f6596991fda5334f63dfb9b8027849 /SRC/clalsd.f
parent5fe0466a14e395641f4f8a300ecc9dcb8058081b (diff)
Integrating Doxygen in comments
Diffstat (limited to 'SRC/clalsd.f')
-rw-r--r--SRC/clalsd.f280
1 files changed, 185 insertions, 95 deletions
diff --git a/SRC/clalsd.f b/SRC/clalsd.f
index bfaa0f8a..64ad5478 100644
--- a/SRC/clalsd.f
+++ b/SRC/clalsd.f
@@ -1,10 +1,193 @@
+*> \brief \b CLALSD
+*
+* =========== DOCUMENTATION ===========
+*
+* Online html documentation available at
+* http://www.netlib.org/lapack/explore-html/
+*
+* Definition
+* ==========
+*
+* SUBROUTINE CLALSD( UPLO, SMLSIZ, N, NRHS, D, E, B, LDB, RCOND,
+* RANK, WORK, RWORK, IWORK, INFO )
+*
+* .. Scalar Arguments ..
+* CHARACTER UPLO
+* INTEGER INFO, LDB, N, NRHS, RANK, SMLSIZ
+* REAL RCOND
+* ..
+* .. Array Arguments ..
+* INTEGER IWORK( * )
+* REAL D( * ), E( * ), RWORK( * )
+* COMPLEX B( LDB, * ), WORK( * )
+* ..
+*
+* Purpose
+* =======
+*
+*>\details \b Purpose:
+*>\verbatim
+*>
+*> CLALSD uses the singular value decomposition of A to solve the least
+*> squares problem of finding X to minimize the Euclidean norm of each
+*> column of A*X-B, where A is N-by-N upper bidiagonal, and X and B
+*> are N-by-NRHS. The solution X overwrites B.
+*>
+*> The singular values of A smaller than RCOND times the largest
+*> singular value are treated as zero in solving the least squares
+*> problem; in this case a minimum norm solution is returned.
+*> The actual singular values are returned in D in ascending order.
+*>
+*> This code 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 XMP, Cray YMP, 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] UPLO
+*> \verbatim
+*> UPLO is CHARACTER*1
+*> = 'U': D and E define an upper bidiagonal matrix.
+*> = 'L': D and E define a lower bidiagonal matrix.
+*> \endverbatim
+*>
+*> \param[in] SMLSIZ
+*> \verbatim
+*> SMLSIZ is INTEGER
+*> The maximum size of the subproblems at the bottom of the
+*> computation tree.
+*> \endverbatim
+*>
+*> \param[in] N
+*> \verbatim
+*> N is INTEGER
+*> The dimension of the bidiagonal matrix. N >= 0.
+*> \endverbatim
+*>
+*> \param[in] NRHS
+*> \verbatim
+*> NRHS is INTEGER
+*> The number of columns of B. NRHS must be at least 1.
+*> \endverbatim
+*>
+*> \param[in,out] D
+*> \verbatim
+*> D is REAL array, dimension (N)
+*> On entry D contains the main diagonal of the bidiagonal
+*> matrix. On exit, if INFO = 0, D contains its singular values.
+*> \endverbatim
+*>
+*> \param[in,out] E
+*> \verbatim
+*> E is REAL array, dimension (N-1)
+*> Contains the super-diagonal entries of the bidiagonal matrix.
+*> On exit, E has been destroyed.
+*> \endverbatim
+*>
+*> \param[in,out] B
+*> \verbatim
+*> B is COMPLEX array, dimension (LDB,NRHS)
+*> On input, B contains the right hand sides of the least
+*> squares problem. On output, B contains the solution X.
+*> \endverbatim
+*>
+*> \param[in] LDB
+*> \verbatim
+*> LDB is INTEGER
+*> The leading dimension of B in the calling subprogram.
+*> LDB must be at least max(1,N).
+*> \endverbatim
+*>
+*> \param[in] RCOND
+*> \verbatim
+*> RCOND is REAL
+*> The singular values of A less than or equal to RCOND times
+*> the largest singular value are treated as zero in solving
+*> the least squares problem. If RCOND is negative,
+*> machine precision is used instead.
+*> For example, if diag(S)*X=B were the least squares problem,
+*> where diag(S) is a diagonal matrix of singular values, the
+*> solution would be X(i) = B(i) / S(i) if S(i) is greater than
+*> RCOND*max(S), and X(i) = 0 if S(i) is less than or equal to
+*> RCOND*max(S).
+*> \endverbatim
+*>
+*> \param[out] RANK
+*> \verbatim
+*> RANK is INTEGER
+*> The number of singular values of A greater than RCOND times
+*> the largest singular value.
+*> \endverbatim
+*>
+*> \param[out] WORK
+*> \verbatim
+*> WORK is COMPLEX array, dimension (N * NRHS).
+*> \endverbatim
+*>
+*> \param[out] RWORK
+*> \verbatim
+*> RWORK is REAL array, dimension at least
+*> (9*N + 2*N*SMLSIZ + 8*N*NLVL + 3*SMLSIZ*NRHS +
+*> MAX( (SMLSIZ+1)**2, N*(1+NRHS) + 2*NRHS ),
+*> where
+*> NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 )
+*> \endverbatim
+*>
+*> \param[out] IWORK
+*> \verbatim
+*> IWORK is INTEGER array, dimension (3*N*NLVL + 11*N).
+*> \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 failed to compute a singular value while
+*> working on the submatrix lying in rows and columns
+*> INFO/(N+1) through MOD(INFO,N+1).
+*> \endverbatim
+*>
+*
+* Authors
+* =======
+*
+*> \author Univ. of Tennessee
+*> \author Univ. of California Berkeley
+*> \author Univ. of Colorado Denver
+*> \author NAG Ltd.
+*
+*> \date November 2011
+*
+*> \ingroup complexOTHERcomputational
+*
+*
+* Further Details
+* ===============
+*>\details \b Further \b Details
+*> \verbatim
+*>
+*> Based on contributions by
+*> Ming Gu and Ren-Cang Li, Computer Science Division, University of
+*> California at Berkeley, USA
+*> Osni Marques, LBNL/NERSC, USA
+*>
+*> \endverbatim
+*>
+* =====================================================================
SUBROUTINE CLALSD( UPLO, SMLSIZ, N, NRHS, D, E, B, LDB, RCOND,
$ RANK, WORK, RWORK, IWORK, INFO )
*
-* -- LAPACK routine (version 3.3.1) --
+* -- LAPACK computational routine (version 3.3.1) --
* -- LAPACK is a software package provided by Univ. of Tennessee, --
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
-* -- April 2011 --
+* November 2011
*
* .. Scalar Arguments ..
CHARACTER UPLO
@@ -17,99 +200,6 @@
COMPLEX B( LDB, * ), WORK( * )
* ..
*
-* Purpose
-* =======
-*
-* CLALSD uses the singular value decomposition of A to solve the least
-* squares problem of finding X to minimize the Euclidean norm of each
-* column of A*X-B, where A is N-by-N upper bidiagonal, and X and B
-* are N-by-NRHS. The solution X overwrites B.
-*
-* The singular values of A smaller than RCOND times the largest
-* singular value are treated as zero in solving the least squares
-* problem; in this case a minimum norm solution is returned.
-* The actual singular values are returned in D in ascending order.
-*
-* This code 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 XMP, Cray YMP, Cray C 90, or Cray 2.
-* It could conceivably fail on hexadecimal or decimal machines
-* without guard digits, but we know of none.
-*
-* Arguments
-* =========
-*
-* UPLO (input) CHARACTER*1
-* = 'U': D and E define an upper bidiagonal matrix.
-* = 'L': D and E define a lower bidiagonal matrix.
-*
-* SMLSIZ (input) INTEGER
-* The maximum size of the subproblems at the bottom of the
-* computation tree.
-*
-* N (input) INTEGER
-* The dimension of the bidiagonal matrix. N >= 0.
-*
-* NRHS (input) INTEGER
-* The number of columns of B. NRHS must be at least 1.
-*
-* D (input/output) REAL array, dimension (N)
-* On entry D contains the main diagonal of the bidiagonal
-* matrix. On exit, if INFO = 0, D contains its singular values.
-*
-* E (input/output) REAL array, dimension (N-1)
-* Contains the super-diagonal entries of the bidiagonal matrix.
-* On exit, E has been destroyed.
-*
-* B (input/output) COMPLEX array, dimension (LDB,NRHS)
-* On input, B contains the right hand sides of the least
-* squares problem. On output, B contains the solution X.
-*
-* LDB (input) INTEGER
-* The leading dimension of B in the calling subprogram.
-* LDB must be at least max(1,N).
-*
-* RCOND (input) REAL
-* The singular values of A less than or equal to RCOND times
-* the largest singular value are treated as zero in solving
-* the least squares problem. If RCOND is negative,
-* machine precision is used instead.
-* For example, if diag(S)*X=B were the least squares problem,
-* where diag(S) is a diagonal matrix of singular values, the
-* solution would be X(i) = B(i) / S(i) if S(i) is greater than
-* RCOND*max(S), and X(i) = 0 if S(i) is less than or equal to
-* RCOND*max(S).
-*
-* RANK (output) INTEGER
-* The number of singular values of A greater than RCOND times
-* the largest singular value.
-*
-* WORK (workspace) COMPLEX array, dimension (N * NRHS).
-*
-* RWORK (workspace) REAL array, dimension at least
-* (9*N + 2*N*SMLSIZ + 8*N*NLVL + 3*SMLSIZ*NRHS +
-* MAX( (SMLSIZ+1)**2, N*(1+NRHS) + 2*NRHS ),
-* where
-* NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 )
-*
-* IWORK (workspace) INTEGER array, dimension (3*N*NLVL + 11*N).
-*
-* INFO (output) INTEGER
-* = 0: successful exit.
-* < 0: if INFO = -i, the i-th argument had an illegal value.
-* > 0: The algorithm failed to compute a singular value while
-* working on the submatrix lying in rows and columns
-* INFO/(N+1) through MOD(INFO,N+1).
-*
-* 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 ..