1 *> \brief \b DLASD0 computes the singular values of a real upper bidiagonal n-by-m matrix B with diagonal d and off-diagonal e. Used by sbdsdc.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DLASD0 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlasd0.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlasd0.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasd0.f">
21 * SUBROUTINE DLASD0( N, SQRE, D, E, U, LDU, VT, LDVT, SMLSIZ, IWORK,
24 * .. Scalar Arguments ..
25 * INTEGER INFO, LDU, LDVT, N, SMLSIZ, SQRE
27 * .. Array Arguments ..
29 * DOUBLE PRECISION D( * ), E( * ), U( LDU, * ), VT( LDVT, * ),
39 *> Using a divide and conquer approach, DLASD0 computes the singular
40 *> value decomposition (SVD) of a real upper bidiagonal N-by-M
41 *> matrix B with diagonal D and offdiagonal E, where M = N + SQRE.
42 *> The algorithm computes orthogonal matrices U and VT such that
43 *> B = U * S * VT. The singular values S are overwritten on D.
45 *> A related subroutine, DLASDA, computes only the singular values,
46 *> and optionally, the singular vectors in compact form.
55 *> On entry, the row dimension of the upper bidiagonal matrix.
56 *> This is also the dimension of the main diagonal array D.
62 *> Specifies the column dimension of the bidiagonal matrix.
63 *> = 0: The bidiagonal matrix has column dimension M = N;
64 *> = 1: The bidiagonal matrix has column dimension M = N+1;
69 *> D is DOUBLE PRECISION array, dimension (N)
70 *> On entry D contains the main diagonal of the bidiagonal
72 *> On exit D, if INFO = 0, contains its singular values.
77 *> E is DOUBLE PRECISION array, dimension (M-1)
78 *> Contains the subdiagonal entries of the bidiagonal matrix.
79 *> On exit, E has been destroyed.
84 *> U is DOUBLE PRECISION array, dimension at least (LDQ, N)
85 *> On exit, U contains the left singular vectors.
91 *> On entry, leading dimension of U.
96 *> VT is DOUBLE PRECISION array, dimension at least (LDVT, M)
97 *> On exit, VT**T contains the right singular vectors.
103 *> On entry, leading dimension of VT.
109 *> On entry, maximum size of the subproblems at the
110 *> bottom of the computation tree.
115 *> IWORK is INTEGER work array.
116 *> Dimension must be at least (8 * N)
121 *> WORK is DOUBLE PRECISION work array.
122 *> Dimension must be at least (3 * M**2 + 2 * M)
128 *> = 0: successful exit.
129 *> < 0: if INFO = -i, the i-th argument had an illegal value.
130 *> > 0: if INFO = 1, a singular value did not converge
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
141 *> \date November 2015
143 *> \ingroup auxOTHERauxiliary
145 *> \par Contributors:
148 *> Ming Gu and Huan Ren, Computer Science Division, University of
149 *> California at Berkeley, USA
151 * =====================================================================
152 SUBROUTINE DLASD0( N, SQRE, D, E, U, LDU, VT, LDVT, SMLSIZ, IWORK,
155 * -- LAPACK auxiliary routine (version 3.6.0) --
156 * -- LAPACK is a software package provided by Univ. of Tennessee, --
157 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160 * .. Scalar Arguments ..
161 INTEGER INFO, LDU, LDVT, N, SMLSIZ, SQRE
163 * .. Array Arguments ..
165 DOUBLE PRECISION D( * ), E( * ), U( LDU, * ), VT( LDVT, * ),
169 * =====================================================================
171 * .. Local Scalars ..
172 INTEGER I, I1, IC, IDXQ, IDXQC, IM1, INODE, ITEMP, IWK,
173 $ J, LF, LL, LVL, M, NCC, ND, NDB1, NDIML, NDIMR,
174 $ NL, NLF, NLP1, NLVL, NR, NRF, NRP1, SQREI
175 DOUBLE PRECISION ALPHA, BETA
177 * .. External Subroutines ..
178 EXTERNAL DLASD1, DLASDQ, DLASDT, XERBLA
180 * .. Executable Statements ..
182 * Test the input parameters.
188 ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
196 ELSE IF( LDVT.LT.M ) THEN
198 ELSE IF( SMLSIZ.LT.3 ) THEN
202 CALL XERBLA( 'DLASD0', -INFO )
206 * If the input matrix is too small, call DLASDQ to find the SVD.
208 IF( N.LE.SMLSIZ ) THEN
209 CALL DLASDQ( 'U', SQRE, N, M, N, 0, D, E, VT, LDVT, U, LDU, U,
214 * Set up the computation tree.
221 CALL DLASDT( N, NLVL, ND, IWORK( INODE ), IWORK( NDIML ),
222 $ IWORK( NDIMR ), SMLSIZ )
224 * For the nodes on bottom level of the tree, solve
225 * their subproblems by DLASDQ.
231 * IC : center row of each node
232 * NL : number of rows of left subproblem
233 * NR : number of rows of right subproblem
234 * NLF: starting row of the left subproblem
235 * NRF: starting row of the right subproblem
238 IC = IWORK( INODE+I1 )
239 NL = IWORK( NDIML+I1 )
241 NR = IWORK( NDIMR+I1 )
246 CALL DLASDQ( 'U', SQREI, NL, NLP1, NL, NCC, D( NLF ), E( NLF ),
247 $ VT( NLF, NLF ), LDVT, U( NLF, NLF ), LDU,
248 $ U( NLF, NLF ), LDU, WORK, INFO )
252 ITEMP = IDXQ + NLF - 2
262 CALL DLASDQ( 'U', SQREI, NR, NRP1, NR, NCC, D( NRF ), E( NRF ),
263 $ VT( NRF, NRF ), LDVT, U( NRF, NRF ), LDU,
264 $ U( NRF, NRF ), LDU, WORK, INFO )
270 IWORK( ITEMP+J-1 ) = J
274 * Now conquer each subproblem bottom-up.
276 DO 50 LVL = NLVL, 1, -1
278 * Find the first node LF and last node LL on the
290 IC = IWORK( INODE+IM1 )
291 NL = IWORK( NDIML+IM1 )
292 NR = IWORK( NDIMR+IM1 )
294 IF( ( SQRE.EQ.0 ) .AND. ( I.EQ.LL ) ) THEN
299 IDXQC = IDXQ + NLF - 1
302 CALL DLASD1( NL, NR, SQREI, D( NLF ), ALPHA, BETA,
303 $ U( NLF, NLF ), LDU, VT( NLF, NLF ), LDVT,
304 $ IWORK( IDXQC ), IWORK( IWK ), WORK, INFO )
306 * Report the possible convergence failure.