1DLALSA(1)                LAPACK routine (version 3.2)                DLALSA(1)
2
3
4

NAME

6       DLALSA - is an itermediate step in solving the least squares problem by
7       computing the SVD of the coefficient matrix in compact form (The singu‐
8       lar vectors are computed as products of simple orthorgonal matrices.)
9

SYNOPSIS

11       SUBROUTINE DLALSA( ICOMPQ,  SMLSIZ,  N, NRHS, B, LDB, BX, LDBX, U, LDU,
12                          VT, K, DIFL, DIFR, Z, POLES, GIVPTR, GIVCOL, LDGCOL,
13                          PERM, GIVNUM, C, S, WORK, IWORK, INFO )
14
15           INTEGER        ICOMPQ,  INFO, LDB, LDBX, LDGCOL, LDU, N, NRHS, SML‐
16                          SIZ
17
18           INTEGER        GIVCOL( LDGCOL, * ), GIVPTR( * ), IWORK( * ),  K(  *
19                          ), PERM( LDGCOL, * )
20
21           DOUBLE         PRECISION  B( LDB, * ), BX( LDBX, * ), C( * ), DIFL(
22                          LDU, * ), DIFR( LDU, * ), GIVNUM( LDU, *  ),  POLES(
23                          LDU, * ), S( * ), U( LDU, * ), VT( LDU, * ), WORK( *
24                          ), Z( LDU, * )
25

PURPOSE

27       DLALSA is an itermediate step in solving the least squares  problem  by
28       computing the SVD of the coefficient matrix in compact form (The singu‐
29       lar vectors are computed as products of simple orthorgonal  matrices.).
30       If  ICOMPQ  = 0, DLALSA applies the inverse of the left singular vector
31       matrix of an upper bidiagonal matrix to the right  hand  side;  and  if
32       ICOMPQ  =  1,  DLALSA  applies  the right singular vector matrix to the
33       right hand side. The singular vector matrices were generated in compact
34       form by DLALSA.
35

ARGUMENTS

37       ICOMPQ (input) INTEGER Specifies whether the left or the right singular
38       vector matrix is involved.  = 0: Left singular vector matrix
39       = 1: Right singular vector matrix SMLSIZ (input)  INTEGER  The  maximum
40       size of the subproblems at the bottom of the computation tree.
41
42       N      (input) INTEGER
43              The row and column dimensions of the upper bidiagonal matrix.
44
45       NRHS   (input) INTEGER
46              The number of columns of B and BX. NRHS must be at least 1.
47
48       B      (input/output) DOUBLE PRECISION array, dimension ( LDB, NRHS )
49              On  input,  B contains the right hand sides of the least squares
50              problem in rows 1 through M.  On output, B contains the solution
51              X in rows 1 through N.
52
53       LDB    (input) INTEGER
54              The  leading dimension of B in the calling subprogram.  LDB must
55              be at least max(1,MAX( M, N ) ).
56
57       BX     (output) DOUBLE PRECISION array, dimension ( LDBX, NRHS )
58              On exit, the result of applying the left or right singular  vec‐
59              tor matrix to B.
60
61       LDBX   (input) INTEGER
62              The leading dimension of BX.
63
64       U      (input) DOUBLE PRECISION array, dimension ( LDU, SMLSIZ ).
65              On  entry,  U  contains the left singular vector matrices of all
66              subproblems at the bottom level.
67
68       LDU    (input) INTEGER, LDU = > N.
69              The leading dimension  of  arrays  U,  VT,  DIFL,  DIFR,  POLES,
70              GIVNUM, and Z.
71
72       VT     (input) DOUBLE PRECISION array, dimension ( LDU, SMLSIZ+1 ).
73              On entry, VT' contains the right singular vector matrices of all
74              subproblems at the bottom level.
75
76       K      (input) INTEGER array, dimension ( N ).
77
78       DIFL   (input) DOUBLE PRECISION array, dimension ( LDU, NLVL ).
79              where NLVL = INT(log_2 (N/(SMLSIZ+1))) + 1.
80
81       DIFR   (input) DOUBLE PRECISION array, dimension ( LDU, 2 * NLVL ).
82              On entry, DIFL(*, I) and DIFR(*, 2  *  I  -1)  record  distances
83              between singular values on the I-th level and singular values on
84              the (I -1)-th level, and DIFR(*, 2 * I) record  the  normalizing
85              factors of the right singular vectors matrices of subproblems on
86              I-th level.
87
88       Z      (input) DOUBLE PRECISION array, dimension ( LDU, NLVL ).
89              On entry, Z(1, I) contains  the  components  of  the  deflation-
90              adjusted updating row vector for subproblems on the I-th level.
91
92       POLES  (input) DOUBLE PRECISION array, dimension ( LDU, 2 * NLVL ).
93              On  entry,  POLES(*,  2  * I -1: 2 * I) contains the new and old
94              singular values involved in the secular equations  on  the  I-th
95              level.   GIVPTR  (input)  INTEGER  array,  dimension  ( N ).  On
96              entry, GIVPTR( I ) records the number of Givens  rotations  per‐
97              formed  on  the  I-th  problem  on the computation tree.  GIVCOL
98              (input) INTEGER array, dimension (  LDGCOL,  2  *  NLVL  ).   On
99              entry, for each I, GIVCOL(*, 2 * I - 1: 2 * I) records the loca‐
100              tions of Givens rotations performed on the  I-th  level  on  the
101              computation  tree.   LDGCOL  (input) INTEGER, LDGCOL = > N.  The
102              leading dimension of arrays GIVCOL and PERM.
103
104       PERM   (input) INTEGER array, dimension ( LDGCOL, NLVL ).
105              On entry, PERM(*, I) records permutations done on the I-th level
106              of the computation tree.  GIVNUM (input) DOUBLE PRECISION array,
107              dimension ( LDU, 2 * NLVL ).  On entry, GIVNUM(*, 2 *I -1 : 2  *
108              I) records the C- and S- values of Givens rotations performed on
109              the I-th level on the computation tree.
110
111       C      (input) DOUBLE PRECISION array, dimension ( N ).
112              On entry, if the I-th subproblem is not square, C( I )  contains
113              the C-value of a Givens rotation related to the right null space
114              of the I-th subproblem.
115
116       S      (input) DOUBLE PRECISION array, dimension ( N ).
117              On entry, if the I-th subproblem is not square, S( I )  contains
118              the S-value of a Givens rotation related to the right null space
119              of the I-th subproblem.
120
121       WORK   (workspace) DOUBLE PRECISION array.
122              The dimension must be at least N.
123
124       IWORK  (workspace) INTEGER array.
125              The dimension must be at least 3 * N
126
127       INFO   (output) INTEGER
128              = 0:  successful exit.
129              < 0:  if INFO = -i, the i-th argument had an illegal value.
130

FURTHER DETAILS

132       Based on contributions by
133          Ming Gu and Ren-Cang Li, Computer Science Division, University of
134            California at Berkeley, USA
135          Osni Marques, LBNL/NERSC, USA
136
137
138
139 LAPACK routine (version 3.2)    November 2008                       DLALSA(1)
Impressum