1 *> \brief \b DLASD1 computes the SVD of an upper bidiagonal matrix B of the specified size. Used by sbdsdc.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DLASD1 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlasd1.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlasd1.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlasd1.f">
21 * SUBROUTINE DLASD1( NL, NR, SQRE, D, ALPHA, BETA, U, LDU, VT, LDVT,
22 * IDXQ, IWORK, WORK, INFO )
24 * .. Scalar Arguments ..
25 * INTEGER INFO, LDU, LDVT, NL, NR, SQRE
26 * DOUBLE PRECISION ALPHA, BETA
28 * .. Array Arguments ..
29 * INTEGER IDXQ( * ), IWORK( * )
30 * DOUBLE PRECISION D( * ), U( LDU, * ), VT( LDVT, * ), WORK( * )
39 *> DLASD1 computes the SVD of an upper bidiagonal N-by-M matrix B,
40 *> where N = NL + NR + 1 and M = N + SQRE. DLASD1 is called from DLASD0.
42 *> A related subroutine DLASD7 handles the case in which the singular
43 *> values (and the singular vectors in factored form) are desired.
45 *> DLASD1 computes the SVD as follows:
48 *> B = U(in) * ( Z1**T a Z2**T b ) * VT(in)
51 *> = U(out) * ( D(out) 0) * VT(out)
53 *> where Z**T = (Z1**T a Z2**T b) = u**T VT**T, and u is a vector of dimension M
54 *> with ALPHA and BETA in the NL+1 and NL+2 th entries and zeros
55 *> elsewhere; and the entry b is empty if SQRE = 0.
57 *> The left singular vectors of the original matrix are stored in U, and
58 *> the transpose of the right singular vectors are stored in VT, and the
59 *> singular values are in D. The algorithm consists of three stages:
61 *> The first stage consists of deflating the size of the problem
62 *> when there are multiple singular values or when there are zeros in
63 *> the Z vector. For each such occurrence the dimension of the
64 *> secular equation problem is reduced by one. This stage is
65 *> performed by the routine DLASD2.
67 *> The second stage consists of calculating the updated
68 *> singular values. This is done by finding the square roots of the
69 *> roots of the secular equation via the routine DLASD4 (as called
70 *> by DLASD3). This routine also calculates the singular vectors of
71 *> the current problem.
73 *> The final stage consists of computing the updated singular vectors
74 *> directly using the updated singular values. The singular vectors
75 *> for the current problem are multiplied with the singular vectors
76 *> from the overall problem.
85 *> The row dimension of the upper block. NL >= 1.
91 *> The row dimension of the lower block. NR >= 1.
97 *> = 0: the lower block is an NR-by-NR square matrix.
98 *> = 1: the lower block is an NR-by-(NR+1) rectangular matrix.
100 *> The bidiagonal matrix has row dimension N = NL + NR + 1,
101 *> and column dimension M = N + SQRE.
106 *> D is DOUBLE PRECISION array,
107 *> dimension (N = NL+NR+1).
108 *> On entry D(1:NL,1:NL) contains the singular values of the
109 *> upper block; and D(NL+2:N) contains the singular values of
110 *> the lower block. On exit D(1:N) contains the singular values
111 *> of the modified matrix.
114 *> \param[in,out] ALPHA
116 *> ALPHA is DOUBLE PRECISION
117 *> Contains the diagonal element associated with the added row.
120 *> \param[in,out] BETA
122 *> BETA is DOUBLE PRECISION
123 *> Contains the off-diagonal element associated with the added
129 *> U is DOUBLE PRECISION array, dimension(LDU,N)
130 *> On entry U(1:NL, 1:NL) contains the left singular vectors of
131 *> the upper block; U(NL+2:N, NL+2:N) contains the left singular
132 *> vectors of the lower block. On exit U contains the left
133 *> singular vectors of the bidiagonal matrix.
139 *> The leading dimension of the array U. LDU >= max( 1, N ).
144 *> VT is DOUBLE PRECISION array, dimension(LDVT,M)
145 *> where M = N + SQRE.
146 *> On entry VT(1:NL+1, 1:NL+1)**T contains the right singular
147 *> vectors of the upper block; VT(NL+2:M, NL+2:M)**T contains
148 *> the right singular vectors of the lower block. On exit
149 *> VT**T contains the right singular vectors of the
150 *> bidiagonal matrix.
156 *> The leading dimension of the array VT. LDVT >= max( 1, M ).
159 *> \param[in,out] IDXQ
161 *> IDXQ is INTEGER array, dimension(N)
162 *> This contains the permutation which will reintegrate the
163 *> subproblem just solved back into sorted order, i.e.
164 *> D( IDXQ( I = 1, N ) ) will be in ascending order.
169 *> IWORK is INTEGER array, dimension( 4 * N )
174 *> WORK is DOUBLE PRECISION array, dimension( 3*M**2 + 2*M )
180 *> = 0: successful exit.
181 *> < 0: if INFO = -i, the i-th argument had an illegal value.
182 *> > 0: if INFO = 1, a singular value did not converge
188 *> \author Univ. of Tennessee
189 *> \author Univ. of California Berkeley
190 *> \author Univ. of Colorado Denver
195 *> \ingroup OTHERauxiliary
197 *> \par Contributors:
200 *> Ming Gu and Huan Ren, Computer Science Division, University of
201 *> California at Berkeley, USA
203 * =====================================================================
204 SUBROUTINE DLASD1( NL, NR, SQRE, D, ALPHA, BETA, U, LDU, VT, LDVT,
205 $ IDXQ, IWORK, WORK, INFO )
207 * -- LAPACK auxiliary routine (version 3.6.1) --
208 * -- LAPACK is a software package provided by Univ. of Tennessee, --
209 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
212 * .. Scalar Arguments ..
213 INTEGER INFO, LDU, LDVT, NL, NR, SQRE
214 DOUBLE PRECISION ALPHA, BETA
216 * .. Array Arguments ..
217 INTEGER IDXQ( * ), IWORK( * )
218 DOUBLE PRECISION D( * ), U( LDU, * ), VT( LDVT, * ), WORK( * )
221 * =====================================================================
225 DOUBLE PRECISION ONE, ZERO
226 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
228 * .. Local Scalars ..
229 INTEGER COLTYP, I, IDX, IDXC, IDXP, IQ, ISIGMA, IU2,
230 $ IVT2, IZ, K, LDQ, LDU2, LDVT2, M, N, N1, N2
231 DOUBLE PRECISION ORGNRM
233 * .. External Subroutines ..
234 EXTERNAL DLAMRG, DLASCL, DLASD2, DLASD3, XERBLA
236 * .. Intrinsic Functions ..
239 * .. Executable Statements ..
241 * Test the input parameters.
247 ELSE IF( NR.LT.1 ) THEN
249 ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
253 CALL XERBLA( 'DLASD1', -INFO )
260 * The following values are for bookkeeping purposes only. They are
261 * integer pointers which indicate the portion of the workspace
262 * used by a particular array in DLASD2 and DLASD3.
280 ORGNRM = MAX( ABS( ALPHA ), ABS( BETA ) )
283 IF( ABS( D( I ) ).GT.ORGNRM ) THEN
284 ORGNRM = ABS( D( I ) )
287 CALL DLASCL( 'G', 0, 0, ORGNRM, ONE, N, 1, D, N, INFO )
288 ALPHA = ALPHA / ORGNRM
291 * Deflate singular values.
293 CALL DLASD2( NL, NR, SQRE, K, D, WORK( IZ ), ALPHA, BETA, U, LDU,
294 $ VT, LDVT, WORK( ISIGMA ), WORK( IU2 ), LDU2,
295 $ WORK( IVT2 ), LDVT2, IWORK( IDXP ), IWORK( IDX ),
296 $ IWORK( IDXC ), IDXQ, IWORK( COLTYP ), INFO )
298 * Solve Secular Equation and update singular vectors.
301 CALL DLASD3( NL, NR, SQRE, K, D, WORK( IQ ), LDQ, WORK( ISIGMA ),
302 $ U, LDU, WORK( IU2 ), LDU2, VT, LDVT, WORK( IVT2 ),
303 $ LDVT2, IWORK( IDXC ), IWORK( COLTYP ), WORK( IZ ),
306 * Report the convergence failure.
314 CALL DLASCL( 'G', 0, 0, ONE, ORGNRM, N, 1, D, N, INFO )
316 * Prepare the IDXQ sorting permutation.
320 CALL DLAMRG( N1, N2, D, 1, -1, IDXQ )