LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine slasdq ( character  UPLO,
integer  SQRE,
integer  N,
integer  NCVT,
integer  NRU,
integer  NCC,
real, dimension( * )  D,
real, dimension( * )  E,
real, dimension( ldvt, * )  VT,
integer  LDVT,
real, dimension( ldu, * )  U,
integer  LDU,
real, dimension( ldc, * )  C,
integer  LDC,
real, dimension( * )  WORK,
integer  INFO 
)

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

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

Purpose:
 SLASDQ 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 REAL 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 REAL 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 REAL 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 REAL 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 REAL 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 REAL 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.
Date
June 2016
Contributors:
Ming Gu and Huan Ren, Computer Science Division, University of California at Berkeley, USA

Definition at line 213 of file slasdq.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: