1ZLALS0(1)                LAPACK routine (version 3.1)                ZLALS0(1)
2
3
4

NAME

6       ZLALS0  -  back the multiplying factors of either the left or the right
7       singular vector matrix of a diagonal matrix appended by a  row  to  the
8       right hand side matrix B in solving the least squares problem using the
9       divide-and-conquer SVD approach
10

SYNOPSIS

12       SUBROUTINE ZLALS0( ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX, LDBX,  PERM,
13                          GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, POLES, DIFL,
14                          DIFR, Z, K, C, S, RWORK, INFO )
15
16           INTEGER        GIVPTR, ICOMPQ, INFO, K, LDB, LDBX, LDGCOL,  LDGNUM,
17                          NL, NR, NRHS, SQRE
18
19           DOUBLE         PRECISION C, S
20
21           INTEGER        GIVCOL( LDGCOL, * ), PERM( * )
22
23           DOUBLE         PRECISION  DIFL(  *  ),  DIFR(  LDGNUM, * ), GIVNUM(
24                          LDGNUM, * ), POLES( LDGNUM, * ), RWORK( * ), Z( * )
25
26           COMPLEX*16     B( LDB, * ), BX( LDBX, * )
27

PURPOSE

29       ZLALS0 applies back the multiplying factors of either the left  or  the
30       right  singular vector matrix of a diagonal matrix appended by a row to
31       the right hand side matrix B in solving the least squares problem using
32       the divide-and-conquer SVD approach.
33
34       For the left singular vector matrix, three types of orthogonal matrices
35       are involved:
36
37       (1L) Givens rotations: the number of such rotations is GIVPTR; the
38            pairs of columns/rows they were applied to are stored in GIVCOL;
39            and the C- and S-values of these rotations are stored in GIVNUM.
40
41       (2L) Permutation. The (NL+1)-st row of B is to be moved to the first
42            row, and for J=2:N, PERM(J)-th row of B is to be moved to the
43            J-th row.
44
45       (3L) The left singular vector matrix of the remaining matrix.
46
47       For the right singular vector matrix, four types of orthogonal matrices
48       are involved:
49
50       (1R) The right singular vector matrix of the remaining matrix.
51
52       (2R) If SQRE = 1, one extra Givens rotation to generate the right
53            null space.
54
55       (3R) The inverse transformation of (2L).
56
57       (4R) The inverse transformation of (1L).
58
59

ARGUMENTS

61       ICOMPQ  (input)  INTEGER  Specifies  whether singular vectors are to be
62       computed in factored form:
63       = 0: Left singular vector matrix.
64       = 1: Right singular vector matrix.
65
66       NL     (input) INTEGER
67              The row dimension of the upper block. NL >= 1.
68
69       NR     (input) INTEGER
70              The row dimension of the lower block. NR >= 1.
71
72       SQRE   (input) INTEGER
73              = 0: the lower block is an NR-by-NR square matrix.
74              = 1: the lower block is an NR-by-(NR+1) rectangular matrix.
75
76              The bidiagonal matrix has row dimension N = NL +  NR  +  1,  and
77              column dimension M = N + SQRE.
78
79       NRHS   (input) INTEGER
80              The number of columns of B and BX. NRHS must be at least 1.
81
82       B      (input/output) COMPLEX*16 array, dimension ( LDB, NRHS )
83              On  input,  B contains the right hand sides of the least squares
84              problem in rows 1 through M. On output, B contains the  solution
85              X in rows 1 through N.
86
87       LDB    (input) INTEGER
88              The leading dimension of B. LDB must be at least max(1,MAX( M, N
89              ) ).
90
91       BX     (workspace) COMPLEX*16 array, dimension ( LDBX, NRHS )
92
93       LDBX   (input) INTEGER
94              The leading dimension of BX.
95
96       PERM   (input) INTEGER array, dimension ( N )
97              The permutations (from deflation and sorting) applied to the two
98              blocks.
99
100              GIVPTR (input) INTEGER The number of Givens rotations which took
101              place in this subproblem.
102
103              GIVCOL (input) INTEGER array, dimension ( LDGCOL, 2 ) Each  pair
104              of numbers indicates a pair of rows/columns involved in a Givens
105              rotation.
106
107              LDGCOL (input) INTEGER The leading dimension of GIVCOL, must  be
108              at least N.
109
110              GIVNUM  (input)  DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
111              Each number indicates the C or S value used in the corresponding
112              Givens rotation.
113
114              LDGNUM  (input)  INTEGER  The  leading dimension of arrays DIFR,
115              POLES and GIVNUM, must be at least K.
116
117       POLES  (input) DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
118              On  entry,  POLES(1:K,  1)  contains  the  new  singular  values
119              obtained from solving the secular equation, and POLES(1:K, 2) is
120              an array containing the poles in the secular equation.
121
122       DIFL   (input) DOUBLE PRECISION array, dimension ( K ).
123              On entry, DIFL(I) is the distance between  I-th  updated  (unde‐
124              flated)  singular  value  and the I-th (undeflated) old singular
125              value.
126
127       DIFR   (input) DOUBLE PRECISION array, dimension ( LDGNUM, 2 ).
128              On entry, DIFR(I, 1) contains the distances between I-th updated
129              (undeflated) singular value and the I+1-th (undeflated) old sin‐
130              gular value. And DIFR(I, 2) is the normalizing factor for the I-
131              th right singular vector.
132
133       Z      (input) DOUBLE PRECISION array, dimension ( K )
134              Contain  the  components  of the deflation-adjusted updating row
135              vector.
136
137       K      (input) INTEGER
138              Contains the dimension of the non-deflated matrix, This  is  the
139              order of the related secular equation. 1 <= K <=N.
140
141       C      (input) DOUBLE PRECISION
142              C  contains garbage if SQRE =0 and the C-value of a Givens rota‐
143              tion related to the right null space if SQRE = 1.
144
145       S      (input) DOUBLE PRECISION
146              S contains garbage if SQRE =0 and the S-value of a Givens  rota‐
147              tion related to the right null space if SQRE = 1.
148
149       RWORK  (workspace) DOUBLE PRECISION array, dimension
150              ( K*(1+NRHS) + 2*NRHS )
151
152       INFO   (output) INTEGER
153              = 0:  successful exit.
154              < 0:  if INFO = -i, the i-th argument had an illegal value.
155

FURTHER DETAILS

157       Based on contributions by
158          Ming Gu and Ren-Cang Li, Computer Science Division, University of
159            California at Berkeley, USA
160          Osni Marques, LBNL/NERSC, USA
161
162
163
164
165 LAPACK routine (version 3.1)    November 2006                       ZLALS0(1)
Impressum