LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dlasdq()

subroutine dlasdq ( character  uplo,
integer  sqre,
integer  n,
integer  ncvt,
integer  nru,
integer  ncc,
double precision, dimension( * )  d,
double precision, dimension( * )  e,
double precision, dimension( ldvt, * )  vt,
integer  ldvt,
double precision, dimension( ldu, * )  u,
integer  ldu,
double precision, dimension( ldc, * )  c,
integer  ldc,
double precision, dimension( * )  work,
integer  info 
)

DLASDQ computes the SVD of a real bidiagonal matrix with diagonal d and off-diagonal e. Used by sbdsdc.

Download DLASDQ + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 DLASDQ computes the singular value decomposition (SVD) of a real
 (upper or lower) bidiagonal matrix with diagonal D and offdiagonal
 E, accumulating the transformations if desired. Letting B denote
 the input bidiagonal matrix, the algorithm computes orthogonal
 matrices Q and P such that B = Q * S * P**T (P**T denotes the transpose
 of P). The singular values S are overwritten on D.

 The input matrix U  is changed to U  * Q  if desired.
 The input matrix VT is changed to P**T * VT if desired.
 The input matrix C  is changed to Q**T * C  if desired.

 See "Computing  Small Singular Values of Bidiagonal Matrices With
 Guaranteed High Relative Accuracy," by J. Demmel and W. Kahan,
 LAPACK Working Note #3, for a detailed description of the algorithm.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
        On entry, UPLO specifies whether the input bidiagonal matrix
        is upper or lower bidiagonal, and whether it is square are
        not.
           UPLO = 'U' or 'u'   B is upper bidiagonal.
           UPLO = 'L' or 'l'   B is lower bidiagonal.
[in]SQRE
          SQRE is INTEGER
        = 0: then the input matrix is N-by-N.
        = 1: then the input matrix is N-by-(N+1) if UPLU = 'U' and
             (N+1)-by-N if UPLU = 'L'.

        The bidiagonal matrix has
        N = NL + NR + 1 rows and
        M = N + SQRE >= N columns.
[in]N
          N is INTEGER
        On entry, N specifies the number of rows and columns
        in the matrix. N must be at least 0.
[in]NCVT
          NCVT is INTEGER
        On entry, NCVT specifies the number of columns of
        the matrix VT. NCVT must be at least 0.
[in]NRU
          NRU is INTEGER
        On entry, NRU specifies the number of rows of
        the matrix U. NRU must be at least 0.
[in]NCC
          NCC is INTEGER
        On entry, NCC specifies the number of columns of
        the matrix C. NCC must be at least 0.
[in,out]D
          D is DOUBLE PRECISION array, dimension (N)
        On entry, D contains the diagonal entries of the
        bidiagonal matrix whose SVD is desired. On normal exit,
        D contains the singular values in ascending order.
[in,out]E
          E is DOUBLE PRECISION array.
        dimension is (N-1) if SQRE = 0 and N if SQRE = 1.
        On entry, the entries of E contain the offdiagonal entries
        of the bidiagonal matrix whose SVD is desired. On normal
        exit, E will contain 0. If the algorithm does not converge,
        D and E will contain the diagonal and superdiagonal entries
        of a bidiagonal matrix orthogonally equivalent to the one
        given as input.
[in,out]VT
          VT is DOUBLE PRECISION array, dimension (LDVT, NCVT)
        On entry, contains a matrix which on exit has been
        premultiplied by P**T, dimension N-by-NCVT if SQRE = 0
        and (N+1)-by-NCVT if SQRE = 1 (not referenced if NCVT=0).
[in]LDVT
          LDVT is INTEGER
        On entry, LDVT specifies the leading dimension of VT as
        declared in the calling (sub) program. LDVT must be at
        least 1. If NCVT is nonzero LDVT must also be at least N.
[in,out]U
          U is DOUBLE PRECISION array, dimension (LDU, N)
        On entry, contains a  matrix which on exit has been
        postmultiplied by Q, dimension NRU-by-N if SQRE = 0
        and NRU-by-(N+1) if SQRE = 1 (not referenced if NRU=0).
[in]LDU
          LDU is INTEGER
        On entry, LDU  specifies the leading dimension of U as
        declared in the calling (sub) program. LDU must be at
        least max( 1, NRU ) .
[in,out]C
          C is DOUBLE PRECISION array, dimension (LDC, NCC)
        On entry, contains an N-by-NCC matrix which on exit
        has been premultiplied by Q**T  dimension N-by-NCC if SQRE = 0
        and (N+1)-by-NCC if SQRE = 1 (not referenced if NCC=0).
[in]LDC
          LDC is INTEGER
        On entry, LDC  specifies the leading dimension of C as
        declared in the calling (sub) program. LDC must be at
        least 1. If NCC is nonzero, LDC must also be at least N.
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (4*N)
        Workspace. Only referenced if one of NCVT, NRU, or NCC is
        nonzero, and if N is at least 2.
[out]INFO
          INFO is INTEGER
        On exit, a value of 0 indicates a successful exit.
        If INFO < 0, argument number -INFO is illegal.
        If INFO > 0, the algorithm did not converge, and INFO
        specifies how many superdiagonals did not converge.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Contributors:
Ming Gu and Huan Ren, Computer Science Division, University of California at Berkeley, USA

Definition at line 209 of file dlasdq.f.

211*
212* -- LAPACK auxiliary routine --
213* -- LAPACK is a software package provided by Univ. of Tennessee, --
214* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
215*
216* .. Scalar Arguments ..
217 CHARACTER UPLO
218 INTEGER INFO, LDC, LDU, LDVT, N, NCC, NCVT, NRU, SQRE
219* ..
220* .. Array Arguments ..
221 DOUBLE PRECISION C( LDC, * ), D( * ), E( * ), U( LDU, * ),
222 $ VT( LDVT, * ), WORK( * )
223* ..
224*
225* =====================================================================
226*
227* .. Parameters ..
228 DOUBLE PRECISION ZERO
229 parameter( zero = 0.0d+0 )
230* ..
231* .. Local Scalars ..
232 LOGICAL ROTATE
233 INTEGER I, ISUB, IUPLO, J, NP1, SQRE1
234 DOUBLE PRECISION CS, R, SMIN, SN
235* ..
236* .. External Subroutines ..
237 EXTERNAL dbdsqr, dlartg, dlasr, dswap, xerbla
238* ..
239* .. External Functions ..
240 LOGICAL LSAME
241 EXTERNAL lsame
242* ..
243* .. Intrinsic Functions ..
244 INTRINSIC max
245* ..
246* .. Executable Statements ..
247*
248* Test the input parameters.
249*
250 info = 0
251 iuplo = 0
252 IF( lsame( uplo, 'U' ) )
253 $ iuplo = 1
254 IF( lsame( uplo, 'L' ) )
255 $ iuplo = 2
256 IF( iuplo.EQ.0 ) THEN
257 info = -1
258 ELSE IF( ( sqre.LT.0 ) .OR. ( sqre.GT.1 ) ) THEN
259 info = -2
260 ELSE IF( n.LT.0 ) THEN
261 info = -3
262 ELSE IF( ncvt.LT.0 ) THEN
263 info = -4
264 ELSE IF( nru.LT.0 ) THEN
265 info = -5
266 ELSE IF( ncc.LT.0 ) THEN
267 info = -6
268 ELSE IF( ( ncvt.EQ.0 .AND. ldvt.LT.1 ) .OR.
269 $ ( ncvt.GT.0 .AND. ldvt.LT.max( 1, n ) ) ) THEN
270 info = -10
271 ELSE IF( ldu.LT.max( 1, nru ) ) THEN
272 info = -12
273 ELSE IF( ( ncc.EQ.0 .AND. ldc.LT.1 ) .OR.
274 $ ( ncc.GT.0 .AND. ldc.LT.max( 1, n ) ) ) THEN
275 info = -14
276 END IF
277 IF( info.NE.0 ) THEN
278 CALL xerbla( 'DLASDQ', -info )
279 RETURN
280 END IF
281 IF( n.EQ.0 )
282 $ RETURN
283*
284* ROTATE is true if any singular vectors desired, false otherwise
285*
286 rotate = ( ncvt.GT.0 ) .OR. ( nru.GT.0 ) .OR. ( ncc.GT.0 )
287 np1 = n + 1
288 sqre1 = sqre
289*
290* If matrix non-square upper bidiagonal, rotate to be lower
291* bidiagonal. The rotations are on the right.
292*
293 IF( ( iuplo.EQ.1 ) .AND. ( sqre1.EQ.1 ) ) THEN
294 DO 10 i = 1, n - 1
295 CALL dlartg( d( i ), e( i ), cs, sn, r )
296 d( i ) = r
297 e( i ) = sn*d( i+1 )
298 d( i+1 ) = cs*d( i+1 )
299 IF( rotate ) THEN
300 work( i ) = cs
301 work( n+i ) = sn
302 END IF
303 10 CONTINUE
304 CALL dlartg( d( n ), e( n ), cs, sn, r )
305 d( n ) = r
306 e( n ) = zero
307 IF( rotate ) THEN
308 work( n ) = cs
309 work( n+n ) = sn
310 END IF
311 iuplo = 2
312 sqre1 = 0
313*
314* Update singular vectors if desired.
315*
316 IF( ncvt.GT.0 )
317 $ CALL dlasr( 'L', 'V', 'F', np1, ncvt, work( 1 ),
318 $ work( np1 ), vt, ldvt )
319 END IF
320*
321* If matrix lower bidiagonal, rotate to be upper bidiagonal
322* by applying Givens rotations on the left.
323*
324 IF( iuplo.EQ.2 ) THEN
325 DO 20 i = 1, n - 1
326 CALL dlartg( d( i ), e( i ), cs, sn, r )
327 d( i ) = r
328 e( i ) = sn*d( i+1 )
329 d( i+1 ) = cs*d( i+1 )
330 IF( rotate ) THEN
331 work( i ) = cs
332 work( n+i ) = sn
333 END IF
334 20 CONTINUE
335*
336* If matrix (N+1)-by-N lower bidiagonal, one additional
337* rotation is needed.
338*
339 IF( sqre1.EQ.1 ) THEN
340 CALL dlartg( d( n ), e( n ), cs, sn, r )
341 d( n ) = r
342 IF( rotate ) THEN
343 work( n ) = cs
344 work( n+n ) = sn
345 END IF
346 END IF
347*
348* Update singular vectors if desired.
349*
350 IF( nru.GT.0 ) THEN
351 IF( sqre1.EQ.0 ) THEN
352 CALL dlasr( 'R', 'V', 'F', nru, n, work( 1 ),
353 $ work( np1 ), u, ldu )
354 ELSE
355 CALL dlasr( 'R', 'V', 'F', nru, np1, work( 1 ),
356 $ work( np1 ), u, ldu )
357 END IF
358 END IF
359 IF( ncc.GT.0 ) THEN
360 IF( sqre1.EQ.0 ) THEN
361 CALL dlasr( 'L', 'V', 'F', n, ncc, work( 1 ),
362 $ work( np1 ), c, ldc )
363 ELSE
364 CALL dlasr( 'L', 'V', 'F', np1, ncc, work( 1 ),
365 $ work( np1 ), c, ldc )
366 END IF
367 END IF
368 END IF
369*
370* Call DBDSQR to compute the SVD of the reduced real
371* N-by-N upper bidiagonal matrix.
372*
373 CALL dbdsqr( 'U', n, ncvt, nru, ncc, d, e, vt, ldvt, u, ldu, c,
374 $ ldc, work, info )
375*
376* Sort the singular values into ascending order (insertion sort on
377* singular values, but only one transposition per singular vector)
378*
379 DO 40 i = 1, n
380*
381* Scan for smallest D(I).
382*
383 isub = i
384 smin = d( i )
385 DO 30 j = i + 1, n
386 IF( d( j ).LT.smin ) THEN
387 isub = j
388 smin = d( j )
389 END IF
390 30 CONTINUE
391 IF( isub.NE.i ) THEN
392*
393* Swap singular values and vectors.
394*
395 d( isub ) = d( i )
396 d( i ) = smin
397 IF( ncvt.GT.0 )
398 $ CALL dswap( ncvt, vt( isub, 1 ), ldvt, vt( i, 1 ), ldvt )
399 IF( nru.GT.0 )
400 $ CALL dswap( nru, u( 1, isub ), 1, u( 1, i ), 1 )
401 IF( ncc.GT.0 )
402 $ CALL dswap( ncc, c( isub, 1 ), ldc, c( i, 1 ), ldc )
403 END IF
404 40 CONTINUE
405*
406 RETURN
407*
408* End of DLASDQ
409*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dbdsqr(uplo, n, ncvt, nru, ncc, d, e, vt, ldvt, u, ldu, c, ldc, work, info)
DBDSQR
Definition dbdsqr.f:241
subroutine dlartg(f, g, c, s, r)
DLARTG generates a plane rotation with real cosine and real sine.
Definition dlartg.f90:111
subroutine dlasr(side, pivot, direct, m, n, c, s, a, lda)
DLASR applies a sequence of plane rotations to a general rectangular matrix.
Definition dlasr.f:199
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dswap(n, dx, incx, dy, incy)
DSWAP
Definition dswap.f:82
Here is the call graph for this function:
Here is the caller graph for this function: