dlasda(3)
NAME
- DLASDA - a divide and conquer approach, DLASDA computes
- the singular value decomposition (SVD) of a real upper bidiagonal
- N-by-M matrix B with diagonal D and offdiagonal E, where M = N +
- SQRE
SYNOPSIS
SUBROUTINE DLASDA( ICOMPQ, SMLSIZ, N, SQRE, D, E, U, LDU,
VT, K, DIFL, DIFR, Z, POLES, GIVPTR, GIVCOL, LDGCOL, PERM,
GIVNUM, C, S, WORK, IWORK, INFO )
INTEGER ICOMPQ, INFO, LDGCOL, LDU, N, SMLSIZ,
SQRE
INTEGER GIVCOL( LDGCOL, * ), GIVPTR( * ),
IWORK( * ), K( * ), PERM( LDGCOL, * )
DOUBLE PRECISION C( * ), D( * ), DIFL( LDU, *
), DIFR( LDU, * ), E( * ), GIVNUM( LDU, * ), POLES( LDU, * ), S(
* ), U( LDU, * ), VT( LDU, * ), WORK( * ), Z( LDU, * )
PURPOSE
- Using a divide and conquer approach, DLASDA computes the
- singular value decomposition (SVD) of a real upper bidiagonal N
- by-M matrix B with diagonal D and offdiagonal E, where M = N +
- SQRE. The algorithm computes the singular values in the SVD B = U
- * S * VT. The orthogonal matrices U and VT are optionally com
- puted in compact form.
- A related subroutine, DLASD0, computes the singular values
- and the singular vectors in explicit form.
ARGUMENTS
- ICOMPQ (input) INTEGER Specifies whether singular vectors
- are to be computed in compact form, as follows = 0: Compute sin
- gular values only.
= 1: Compute singular vectors of upper bidiagonal matrix
- in compact form.
- SMLSIZ (input) INTEGER The maximum size of the subproblems
- at the bottom of the computation tree.
- N (input) INTEGER
- The row dimension of the upper bidiagonal matrix.
- This is also the dimension of the main diagonal array D.
- SQRE (input) INTEGER
- Specifies the column dimension of the bidiagonal
- matrix. = 0: The bidiagonal matrix has column dimension M = N;
= 1: The bidiagonal matrix has column dimension M =
- N + 1.
- D (input/output) DOUBLE PRECISION array, dimension (
- N )
- On entry D contains the main diagonal of the bidi
- agonal matrix. On exit D, if INFO = 0, contains its singular val
- ues.
- E (input) DOUBLE PRECISION array, dimension ( M-1 )
- Contains the subdiagonal entries of the bidiagonal
- matrix. On exit, E has been destroyed.
- U (output) DOUBLE PRECISION array,
- dimension ( LDU, SMLSIZ ) if ICOMPQ = 1, and not
- referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, U contains the
- left singular vector matrices of all subproblems at the bottom
- level.
- LDU (input) INTEGER, LDU = > N.
- The leading dimension of arrays U, VT, DIFL, DIFR,
- POLES, GIVNUM, and Z.
- VT (output) DOUBLE PRECISION array,
- dimension ( LDU, SMLSIZ+1 ) if ICOMPQ = 1, and not
- referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, VT' contains
- the right singular vector matrices of all subproblems at the bot
- tom level.
- K (output) INTEGER array,
- dimension ( N ) if ICOMPQ = 1 and dimension 1 if
- ICOMPQ = 0. If ICOMPQ = 1, on exit, K(I) is the dimension of the
- I-th secular equation on the computation tree.
- DIFL (output) DOUBLE PRECISION array, dimension ( LDU,
- NLVL ),
- where NLVL = floor(log_2 (N/SMLSIZ))).
- DIFR (output) DOUBLE PRECISION array,
- dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1 and di
- mension ( N ) if ICOMPQ = 0. If ICOMPQ = 1, on exit, DIFL(1:N,
- I) and DIFR(1:N, 2 * I - 1) record distances between singular
- values on the I-th level and singular values on the (I -1)-th
- level, and DIFR(1:N, 2 * I ) contains the normalizing factors for
- the right singular vector matrix. See DLASD8 for details.
- Z (output) DOUBLE PRECISION array,
- dimension ( LDU, NLVL ) if ICOMPQ = 1 and dimension
- ( N ) if ICOMPQ = 0. The first K elements of Z(1, I) contain the
- components of the deflation-adjusted updating row vector for sub
- problems on the I-th level.
- POLES (output) DOUBLE PRECISION array,
- dimension ( LDU, 2 * NLVL ) if ICOMPQ = 1, and not
- referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, POLES(1, 2*I
- 1) and POLES(1, 2*I) contain the new and old singular values in
- volved in the secular equations on the I-th level.
- GIVPTR (output) INTEGER array, dimension ( N ) if
- ICOMPQ = 1, and not referenced if ICOMPQ = 0. If ICOMPQ = 1, on
- exit, GIVPTR( I ) records the number of Givens rotations per
- formed on the I-th problem on the computation tree.
- GIVCOL (output) INTEGER array, dimension ( LDGCOL,
- 2 * NLVL ) if ICOMPQ = 1, and not referenced if ICOMPQ = 0. If
- ICOMPQ = 1, on exit, for each I, GIVCOL(1, 2 *I - 1) and GIV
- COL(1, 2 *I) record the locations of Givens rotations performed
- on the I-th level on the computation tree.
- LDGCOL (input) INTEGER, LDGCOL = > N. The leading
- dimension of arrays GIVCOL and PERM.
- PERM (output) INTEGER array,
- dimension ( LDGCOL, NLVL ) if ICOMPQ = 1, and not
- referenced if ICOMPQ = 0. If ICOMPQ = 1, on exit, PERM(1, I)
- records permutations done on the I-th level of the computation
- tree.
- GIVNUM (output) DOUBLE PRECISION array, dimension (
- LDU, 2 * NLVL ) if ICOMPQ = 1, and not referenced if ICOMPQ = 0.
- If ICOMPQ = 1, on exit, for each I, GIVNUM(1, 2 *I - 1) and
- GIVNUM(1, 2 *I) record the C- and S- values of Givens rotations
- performed on the I-th level on the computation tree.
- C (output) DOUBLE PRECISION array,
- dimension ( N ) if ICOMPQ = 1, and dimension 1 if
- ICOMPQ = 0. If ICOMPQ = 1 and the I-th subproblem is not square,
- on exit, C( I ) contains the C-value of a Givens rotation related
- to the right null space of the I-th subproblem.
- S (output) DOUBLE PRECISION array, dimension ( N ) if
- ICOMPQ = 1, and dimension 1 if ICOMPQ = 0. If ICOM
- PQ = 1 and the I-th subproblem is not square, on exit, S( I )
- contains the S-value of a Givens rotation related to the right
- null space of the I-th subproblem.
- WORK (workspace) DOUBLE PRECISION array, dimension
- (6 * N + (SMLSIZ + 1)*(SMLSIZ + 1)).
- IWORK (workspace) INTEGER array.
- Dimension must be at least (7 * N).
- INFO (output) INTEGER
- = 0: successful exit.
< 0: if INFO = -i, the i-th argument had an ille
- gal value.
> 0: if INFO = 1, an singular value did not con
- verge
FURTHER DETAILS
- Based on contributions by
- Ming Gu and Huan Ren, Computer Science Division, Uni
- versity of
California at Berkeley, USA
- LAPACK version 3.0 15 June 2000