Statistiques
| Révision :

root / src / lapack / double / dlals0.f @ 11

Historique | Voir | Annoter | Télécharger (12,78 ko)

1 1 pfleura2
      SUBROUTINE DLALS0( ICOMPQ, NL, NR, SQRE, NRHS, B, LDB, BX, LDBX,
2 1 pfleura2
     $                   PERM, GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM,
3 1 pfleura2
     $                   POLES, DIFL, DIFR, Z, K, C, S, WORK, INFO )
4 1 pfleura2
*
5 1 pfleura2
*  -- LAPACK routine (version 3.2) --
6 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
7 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
8 1 pfleura2
*     November 2006
9 1 pfleura2
*
10 1 pfleura2
*     .. Scalar Arguments ..
11 1 pfleura2
      INTEGER            GIVPTR, ICOMPQ, INFO, K, LDB, LDBX, LDGCOL,
12 1 pfleura2
     $                   LDGNUM, NL, NR, NRHS, SQRE
13 1 pfleura2
      DOUBLE PRECISION   C, S
14 1 pfleura2
*     ..
15 1 pfleura2
*     .. Array Arguments ..
16 1 pfleura2
      INTEGER            GIVCOL( LDGCOL, * ), PERM( * )
17 1 pfleura2
      DOUBLE PRECISION   B( LDB, * ), BX( LDBX, * ), DIFL( * ),
18 1 pfleura2
     $                   DIFR( LDGNUM, * ), GIVNUM( LDGNUM, * ),
19 1 pfleura2
     $                   POLES( LDGNUM, * ), WORK( * ), Z( * )
20 1 pfleura2
*     ..
21 1 pfleura2
*
22 1 pfleura2
*  Purpose
23 1 pfleura2
*  =======
24 1 pfleura2
*
25 1 pfleura2
*  DLALS0 applies back the multiplying factors of either the left or the
26 1 pfleura2
*  right singular vector matrix of a diagonal matrix appended by a row
27 1 pfleura2
*  to the right hand side matrix B in solving the least squares problem
28 1 pfleura2
*  using the divide-and-conquer SVD approach.
29 1 pfleura2
*
30 1 pfleura2
*  For the left singular vector matrix, three types of orthogonal
31 1 pfleura2
*  matrices are involved:
32 1 pfleura2
*
33 1 pfleura2
*  (1L) Givens rotations: the number of such rotations is GIVPTR; the
34 1 pfleura2
*       pairs of columns/rows they were applied to are stored in GIVCOL;
35 1 pfleura2
*       and the C- and S-values of these rotations are stored in GIVNUM.
36 1 pfleura2
*
37 1 pfleura2
*  (2L) Permutation. The (NL+1)-st row of B is to be moved to the first
38 1 pfleura2
*       row, and for J=2:N, PERM(J)-th row of B is to be moved to the
39 1 pfleura2
*       J-th row.
40 1 pfleura2
*
41 1 pfleura2
*  (3L) The left singular vector matrix of the remaining matrix.
42 1 pfleura2
*
43 1 pfleura2
*  For the right singular vector matrix, four types of orthogonal
44 1 pfleura2
*  matrices are involved:
45 1 pfleura2
*
46 1 pfleura2
*  (1R) The right singular vector matrix of the remaining matrix.
47 1 pfleura2
*
48 1 pfleura2
*  (2R) If SQRE = 1, one extra Givens rotation to generate the right
49 1 pfleura2
*       null space.
50 1 pfleura2
*
51 1 pfleura2
*  (3R) The inverse transformation of (2L).
52 1 pfleura2
*
53 1 pfleura2
*  (4R) The inverse transformation of (1L).
54 1 pfleura2
*
55 1 pfleura2
*  Arguments
56 1 pfleura2
*  =========
57 1 pfleura2
*
58 1 pfleura2
*  ICOMPQ (input) INTEGER
59 1 pfleura2
*         Specifies whether singular vectors are to be computed in
60 1 pfleura2
*         factored form:
61 1 pfleura2
*         = 0: Left singular vector matrix.
62 1 pfleura2
*         = 1: Right singular vector matrix.
63 1 pfleura2
*
64 1 pfleura2
*  NL     (input) INTEGER
65 1 pfleura2
*         The row dimension of the upper block. NL >= 1.
66 1 pfleura2
*
67 1 pfleura2
*  NR     (input) INTEGER
68 1 pfleura2
*         The row dimension of the lower block. NR >= 1.
69 1 pfleura2
*
70 1 pfleura2
*  SQRE   (input) INTEGER
71 1 pfleura2
*         = 0: the lower block is an NR-by-NR square matrix.
72 1 pfleura2
*         = 1: the lower block is an NR-by-(NR+1) rectangular matrix.
73 1 pfleura2
*
74 1 pfleura2
*         The bidiagonal matrix has row dimension N = NL + NR + 1,
75 1 pfleura2
*         and column dimension M = N + SQRE.
76 1 pfleura2
*
77 1 pfleura2
*  NRHS   (input) INTEGER
78 1 pfleura2
*         The number of columns of B and BX. NRHS must be at least 1.
79 1 pfleura2
*
80 1 pfleura2
*  B      (input/output) DOUBLE PRECISION array, dimension ( LDB, NRHS )
81 1 pfleura2
*         On input, B contains the right hand sides of the least
82 1 pfleura2
*         squares problem in rows 1 through M. On output, B contains
83 1 pfleura2
*         the solution X in rows 1 through N.
84 1 pfleura2
*
85 1 pfleura2
*  LDB    (input) INTEGER
86 1 pfleura2
*         The leading dimension of B. LDB must be at least
87 1 pfleura2
*         max(1,MAX( M, N ) ).
88 1 pfleura2
*
89 1 pfleura2
*  BX     (workspace) DOUBLE PRECISION array, dimension ( LDBX, NRHS )
90 1 pfleura2
*
91 1 pfleura2
*  LDBX   (input) INTEGER
92 1 pfleura2
*         The leading dimension of BX.
93 1 pfleura2
*
94 1 pfleura2
*  PERM   (input) INTEGER array, dimension ( N )
95 1 pfleura2
*         The permutations (from deflation and sorting) applied
96 1 pfleura2
*         to the two blocks.
97 1 pfleura2
*
98 1 pfleura2
*  GIVPTR (input) INTEGER
99 1 pfleura2
*         The number of Givens rotations which took place in this
100 1 pfleura2
*         subproblem.
101 1 pfleura2
*
102 1 pfleura2
*  GIVCOL (input) INTEGER array, dimension ( LDGCOL, 2 )
103 1 pfleura2
*         Each pair of numbers indicates a pair of rows/columns
104 1 pfleura2
*         involved in a Givens rotation.
105 1 pfleura2
*
106 1 pfleura2
*  LDGCOL (input) INTEGER
107 1 pfleura2
*         The leading dimension of GIVCOL, must be at least N.
108 1 pfleura2
*
109 1 pfleura2
*  GIVNUM (input) DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
110 1 pfleura2
*         Each number indicates the C or S value used in the
111 1 pfleura2
*         corresponding Givens rotation.
112 1 pfleura2
*
113 1 pfleura2
*  LDGNUM (input) INTEGER
114 1 pfleura2
*         The leading dimension of arrays DIFR, POLES and
115 1 pfleura2
*         GIVNUM, must be at least K.
116 1 pfleura2
*
117 1 pfleura2
*  POLES  (input) DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
118 1 pfleura2
*         On entry, POLES(1:K, 1) contains the new singular
119 1 pfleura2
*         values obtained from solving the secular equation, and
120 1 pfleura2
*         POLES(1:K, 2) is an array containing the poles in the secular
121 1 pfleura2
*         equation.
122 1 pfleura2
*
123 1 pfleura2
*  DIFL   (input) DOUBLE PRECISION array, dimension ( K ).
124 1 pfleura2
*         On entry, DIFL(I) is the distance between I-th updated
125 1 pfleura2
*         (undeflated) singular value and the I-th (undeflated) old
126 1 pfleura2
*         singular value.
127 1 pfleura2
*
128 1 pfleura2
*  DIFR   (input) DOUBLE PRECISION array, dimension ( LDGNUM, 2 ).
129 1 pfleura2
*         On entry, DIFR(I, 1) contains the distances between I-th
130 1 pfleura2
*         updated (undeflated) singular value and the I+1-th
131 1 pfleura2
*         (undeflated) old singular value. And DIFR(I, 2) is the
132 1 pfleura2
*         normalizing factor for the I-th right singular vector.
133 1 pfleura2
*
134 1 pfleura2
*  Z      (input) DOUBLE PRECISION array, dimension ( K )
135 1 pfleura2
*         Contain the components of the deflation-adjusted updating row
136 1 pfleura2
*         vector.
137 1 pfleura2
*
138 1 pfleura2
*  K      (input) INTEGER
139 1 pfleura2
*         Contains the dimension of the non-deflated matrix,
140 1 pfleura2
*         This is the order of the related secular equation. 1 <= K <=N.
141 1 pfleura2
*
142 1 pfleura2
*  C      (input) DOUBLE PRECISION
143 1 pfleura2
*         C contains garbage if SQRE =0 and the C-value of a Givens
144 1 pfleura2
*         rotation related to the right null space if SQRE = 1.
145 1 pfleura2
*
146 1 pfleura2
*  S      (input) DOUBLE PRECISION
147 1 pfleura2
*         S contains garbage if SQRE =0 and the S-value of a Givens
148 1 pfleura2
*         rotation related to the right null space if SQRE = 1.
149 1 pfleura2
*
150 1 pfleura2
*  WORK   (workspace) DOUBLE PRECISION array, dimension ( K )
151 1 pfleura2
*
152 1 pfleura2
*  INFO   (output) INTEGER
153 1 pfleura2
*          = 0:  successful exit.
154 1 pfleura2
*          < 0:  if INFO = -i, the i-th argument had an illegal value.
155 1 pfleura2
*
156 1 pfleura2
*  Further Details
157 1 pfleura2
*  ===============
158 1 pfleura2
*
159 1 pfleura2
*  Based on contributions by
160 1 pfleura2
*     Ming Gu and Ren-Cang Li, Computer Science Division, University of
161 1 pfleura2
*       California at Berkeley, USA
162 1 pfleura2
*     Osni Marques, LBNL/NERSC, USA
163 1 pfleura2
*
164 1 pfleura2
*  =====================================================================
165 1 pfleura2
*
166 1 pfleura2
*     .. Parameters ..
167 1 pfleura2
      DOUBLE PRECISION   ONE, ZERO, NEGONE
168 1 pfleura2
      PARAMETER          ( ONE = 1.0D0, ZERO = 0.0D0, NEGONE = -1.0D0 )
169 1 pfleura2
*     ..
170 1 pfleura2
*     .. Local Scalars ..
171 1 pfleura2
      INTEGER            I, J, M, N, NLP1
172 1 pfleura2
      DOUBLE PRECISION   DIFLJ, DIFRJ, DJ, DSIGJ, DSIGJP, TEMP
173 1 pfleura2
*     ..
174 1 pfleura2
*     .. External Subroutines ..
175 1 pfleura2
      EXTERNAL           DCOPY, DGEMV, DLACPY, DLASCL, DROT, DSCAL,
176 1 pfleura2
     $                   XERBLA
177 1 pfleura2
*     ..
178 1 pfleura2
*     .. External Functions ..
179 1 pfleura2
      DOUBLE PRECISION   DLAMC3, DNRM2
180 1 pfleura2
      EXTERNAL           DLAMC3, DNRM2
181 1 pfleura2
*     ..
182 1 pfleura2
*     .. Intrinsic Functions ..
183 1 pfleura2
      INTRINSIC          MAX
184 1 pfleura2
*     ..
185 1 pfleura2
*     .. Executable Statements ..
186 1 pfleura2
*
187 1 pfleura2
*     Test the input parameters.
188 1 pfleura2
*
189 1 pfleura2
      INFO = 0
190 1 pfleura2
*
191 1 pfleura2
      IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
192 1 pfleura2
         INFO = -1
193 1 pfleura2
      ELSE IF( NL.LT.1 ) THEN
194 1 pfleura2
         INFO = -2
195 1 pfleura2
      ELSE IF( NR.LT.1 ) THEN
196 1 pfleura2
         INFO = -3
197 1 pfleura2
      ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
198 1 pfleura2
         INFO = -4
199 1 pfleura2
      END IF
200 1 pfleura2
*
201 1 pfleura2
      N = NL + NR + 1
202 1 pfleura2
*
203 1 pfleura2
      IF( NRHS.LT.1 ) THEN
204 1 pfleura2
         INFO = -5
205 1 pfleura2
      ELSE IF( LDB.LT.N ) THEN
206 1 pfleura2
         INFO = -7
207 1 pfleura2
      ELSE IF( LDBX.LT.N ) THEN
208 1 pfleura2
         INFO = -9
209 1 pfleura2
      ELSE IF( GIVPTR.LT.0 ) THEN
210 1 pfleura2
         INFO = -11
211 1 pfleura2
      ELSE IF( LDGCOL.LT.N ) THEN
212 1 pfleura2
         INFO = -13
213 1 pfleura2
      ELSE IF( LDGNUM.LT.N ) THEN
214 1 pfleura2
         INFO = -15
215 1 pfleura2
      ELSE IF( K.LT.1 ) THEN
216 1 pfleura2
         INFO = -20
217 1 pfleura2
      END IF
218 1 pfleura2
      IF( INFO.NE.0 ) THEN
219 1 pfleura2
         CALL XERBLA( 'DLALS0', -INFO )
220 1 pfleura2
         RETURN
221 1 pfleura2
      END IF
222 1 pfleura2
*
223 1 pfleura2
      M = N + SQRE
224 1 pfleura2
      NLP1 = NL + 1
225 1 pfleura2
*
226 1 pfleura2
      IF( ICOMPQ.EQ.0 ) THEN
227 1 pfleura2
*
228 1 pfleura2
*        Apply back orthogonal transformations from the left.
229 1 pfleura2
*
230 1 pfleura2
*        Step (1L): apply back the Givens rotations performed.
231 1 pfleura2
*
232 1 pfleura2
         DO 10 I = 1, GIVPTR
233 1 pfleura2
            CALL DROT( NRHS, B( GIVCOL( I, 2 ), 1 ), LDB,
234 1 pfleura2
     $                 B( GIVCOL( I, 1 ), 1 ), LDB, GIVNUM( I, 2 ),
235 1 pfleura2
     $                 GIVNUM( I, 1 ) )
236 1 pfleura2
   10    CONTINUE
237 1 pfleura2
*
238 1 pfleura2
*        Step (2L): permute rows of B.
239 1 pfleura2
*
240 1 pfleura2
         CALL DCOPY( NRHS, B( NLP1, 1 ), LDB, BX( 1, 1 ), LDBX )
241 1 pfleura2
         DO 20 I = 2, N
242 1 pfleura2
            CALL DCOPY( NRHS, B( PERM( I ), 1 ), LDB, BX( I, 1 ), LDBX )
243 1 pfleura2
   20    CONTINUE
244 1 pfleura2
*
245 1 pfleura2
*        Step (3L): apply the inverse of the left singular vector
246 1 pfleura2
*        matrix to BX.
247 1 pfleura2
*
248 1 pfleura2
         IF( K.EQ.1 ) THEN
249 1 pfleura2
            CALL DCOPY( NRHS, BX, LDBX, B, LDB )
250 1 pfleura2
            IF( Z( 1 ).LT.ZERO ) THEN
251 1 pfleura2
               CALL DSCAL( NRHS, NEGONE, B, LDB )
252 1 pfleura2
            END IF
253 1 pfleura2
         ELSE
254 1 pfleura2
            DO 50 J = 1, K
255 1 pfleura2
               DIFLJ = DIFL( J )
256 1 pfleura2
               DJ = POLES( J, 1 )
257 1 pfleura2
               DSIGJ = -POLES( J, 2 )
258 1 pfleura2
               IF( J.LT.K ) THEN
259 1 pfleura2
                  DIFRJ = -DIFR( J, 1 )
260 1 pfleura2
                  DSIGJP = -POLES( J+1, 2 )
261 1 pfleura2
               END IF
262 1 pfleura2
               IF( ( Z( J ).EQ.ZERO ) .OR. ( POLES( J, 2 ).EQ.ZERO ) )
263 1 pfleura2
     $              THEN
264 1 pfleura2
                  WORK( J ) = ZERO
265 1 pfleura2
               ELSE
266 1 pfleura2
                  WORK( J ) = -POLES( J, 2 )*Z( J ) / DIFLJ /
267 1 pfleura2
     $                        ( POLES( J, 2 )+DJ )
268 1 pfleura2
               END IF
269 1 pfleura2
               DO 30 I = 1, J - 1
270 1 pfleura2
                  IF( ( Z( I ).EQ.ZERO ) .OR.
271 1 pfleura2
     $                ( POLES( I, 2 ).EQ.ZERO ) ) THEN
272 1 pfleura2
                     WORK( I ) = ZERO
273 1 pfleura2
                  ELSE
274 1 pfleura2
                     WORK( I ) = POLES( I, 2 )*Z( I ) /
275 1 pfleura2
     $                           ( DLAMC3( POLES( I, 2 ), DSIGJ )-
276 1 pfleura2
     $                           DIFLJ ) / ( POLES( I, 2 )+DJ )
277 1 pfleura2
                  END IF
278 1 pfleura2
   30          CONTINUE
279 1 pfleura2
               DO 40 I = J + 1, K
280 1 pfleura2
                  IF( ( Z( I ).EQ.ZERO ) .OR.
281 1 pfleura2
     $                ( POLES( I, 2 ).EQ.ZERO ) ) THEN
282 1 pfleura2
                     WORK( I ) = ZERO
283 1 pfleura2
                  ELSE
284 1 pfleura2
                     WORK( I ) = POLES( I, 2 )*Z( I ) /
285 1 pfleura2
     $                           ( DLAMC3( POLES( I, 2 ), DSIGJP )+
286 1 pfleura2
     $                           DIFRJ ) / ( POLES( I, 2 )+DJ )
287 1 pfleura2
                  END IF
288 1 pfleura2
   40          CONTINUE
289 1 pfleura2
               WORK( 1 ) = NEGONE
290 1 pfleura2
               TEMP = DNRM2( K, WORK, 1 )
291 1 pfleura2
               CALL DGEMV( 'T', K, NRHS, ONE, BX, LDBX, WORK, 1, ZERO,
292 1 pfleura2
     $                     B( J, 1 ), LDB )
293 1 pfleura2
               CALL DLASCL( 'G', 0, 0, TEMP, ONE, 1, NRHS, B( J, 1 ),
294 1 pfleura2
     $                      LDB, INFO )
295 1 pfleura2
   50       CONTINUE
296 1 pfleura2
         END IF
297 1 pfleura2
*
298 1 pfleura2
*        Move the deflated rows of BX to B also.
299 1 pfleura2
*
300 1 pfleura2
         IF( K.LT.MAX( M, N ) )
301 1 pfleura2
     $      CALL DLACPY( 'A', N-K, NRHS, BX( K+1, 1 ), LDBX,
302 1 pfleura2
     $                   B( K+1, 1 ), LDB )
303 1 pfleura2
      ELSE
304 1 pfleura2
*
305 1 pfleura2
*        Apply back the right orthogonal transformations.
306 1 pfleura2
*
307 1 pfleura2
*        Step (1R): apply back the new right singular vector matrix
308 1 pfleura2
*        to B.
309 1 pfleura2
*
310 1 pfleura2
         IF( K.EQ.1 ) THEN
311 1 pfleura2
            CALL DCOPY( NRHS, B, LDB, BX, LDBX )
312 1 pfleura2
         ELSE
313 1 pfleura2
            DO 80 J = 1, K
314 1 pfleura2
               DSIGJ = POLES( J, 2 )
315 1 pfleura2
               IF( Z( J ).EQ.ZERO ) THEN
316 1 pfleura2
                  WORK( J ) = ZERO
317 1 pfleura2
               ELSE
318 1 pfleura2
                  WORK( J ) = -Z( J ) / DIFL( J ) /
319 1 pfleura2
     $                        ( DSIGJ+POLES( J, 1 ) ) / DIFR( J, 2 )
320 1 pfleura2
               END IF
321 1 pfleura2
               DO 60 I = 1, J - 1
322 1 pfleura2
                  IF( Z( J ).EQ.ZERO ) THEN
323 1 pfleura2
                     WORK( I ) = ZERO
324 1 pfleura2
                  ELSE
325 1 pfleura2
                     WORK( I ) = Z( J ) / ( DLAMC3( DSIGJ, -POLES( I+1,
326 1 pfleura2
     $                           2 ) )-DIFR( I, 1 ) ) /
327 1 pfleura2
     $                           ( DSIGJ+POLES( I, 1 ) ) / DIFR( I, 2 )
328 1 pfleura2
                  END IF
329 1 pfleura2
   60          CONTINUE
330 1 pfleura2
               DO 70 I = J + 1, K
331 1 pfleura2
                  IF( Z( J ).EQ.ZERO ) THEN
332 1 pfleura2
                     WORK( I ) = ZERO
333 1 pfleura2
                  ELSE
334 1 pfleura2
                     WORK( I ) = Z( J ) / ( DLAMC3( DSIGJ, -POLES( I,
335 1 pfleura2
     $                           2 ) )-DIFL( I ) ) /
336 1 pfleura2
     $                           ( DSIGJ+POLES( I, 1 ) ) / DIFR( I, 2 )
337 1 pfleura2
                  END IF
338 1 pfleura2
   70          CONTINUE
339 1 pfleura2
               CALL DGEMV( 'T', K, NRHS, ONE, B, LDB, WORK, 1, ZERO,
340 1 pfleura2
     $                     BX( J, 1 ), LDBX )
341 1 pfleura2
   80       CONTINUE
342 1 pfleura2
         END IF
343 1 pfleura2
*
344 1 pfleura2
*        Step (2R): if SQRE = 1, apply back the rotation that is
345 1 pfleura2
*        related to the right null space of the subproblem.
346 1 pfleura2
*
347 1 pfleura2
         IF( SQRE.EQ.1 ) THEN
348 1 pfleura2
            CALL DCOPY( NRHS, B( M, 1 ), LDB, BX( M, 1 ), LDBX )
349 1 pfleura2
            CALL DROT( NRHS, BX( 1, 1 ), LDBX, BX( M, 1 ), LDBX, C, S )
350 1 pfleura2
         END IF
351 1 pfleura2
         IF( K.LT.MAX( M, N ) )
352 1 pfleura2
     $      CALL DLACPY( 'A', N-K, NRHS, B( K+1, 1 ), LDB, BX( K+1, 1 ),
353 1 pfleura2
     $                   LDBX )
354 1 pfleura2
*
355 1 pfleura2
*        Step (3R): permute rows of B.
356 1 pfleura2
*
357 1 pfleura2
         CALL DCOPY( NRHS, BX( 1, 1 ), LDBX, B( NLP1, 1 ), LDB )
358 1 pfleura2
         IF( SQRE.EQ.1 ) THEN
359 1 pfleura2
            CALL DCOPY( NRHS, BX( M, 1 ), LDBX, B( M, 1 ), LDB )
360 1 pfleura2
         END IF
361 1 pfleura2
         DO 90 I = 2, N
362 1 pfleura2
            CALL DCOPY( NRHS, BX( I, 1 ), LDBX, B( PERM( I ), 1 ), LDB )
363 1 pfleura2
   90    CONTINUE
364 1 pfleura2
*
365 1 pfleura2
*        Step (4R): apply back the Givens rotations performed.
366 1 pfleura2
*
367 1 pfleura2
         DO 100 I = GIVPTR, 1, -1
368 1 pfleura2
            CALL DROT( NRHS, B( GIVCOL( I, 2 ), 1 ), LDB,
369 1 pfleura2
     $                 B( GIVCOL( I, 1 ), 1 ), LDB, GIVNUM( I, 2 ),
370 1 pfleura2
     $                 -GIVNUM( I, 1 ) )
371 1 pfleura2
  100    CONTINUE
372 1 pfleura2
      END IF
373 1 pfleura2
*
374 1 pfleura2
      RETURN
375 1 pfleura2
*
376 1 pfleura2
*     End of DLALS0
377 1 pfleura2
*
378 1 pfleura2
      END