root / src / lapack / double / dgelsd.f @ 2
Historique | Voir | Annoter | Télécharger (18,5 ko)
1 |
SUBROUTINE DGELSD( M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, |
---|---|
2 |
$ WORK, LWORK, IWORK, INFO ) |
3 |
* |
4 |
* -- LAPACK driver routine (version 3.2.2) -- |
5 |
* -- LAPACK is a software package provided by Univ. of Tennessee, -- |
6 |
* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- |
7 |
* June 2010 |
8 |
* |
9 |
* .. Scalar Arguments .. |
10 |
INTEGER INFO, LDA, LDB, LWORK, M, N, NRHS, RANK |
11 |
DOUBLE PRECISION RCOND |
12 |
* .. |
13 |
* .. Array Arguments .. |
14 |
INTEGER IWORK( * ) |
15 |
DOUBLE PRECISION A( LDA, * ), B( LDB, * ), S( * ), WORK( * ) |
16 |
* .. |
17 |
* |
18 |
* Purpose |
19 |
* ======= |
20 |
* |
21 |
* DGELSD computes the minimum-norm solution to a real linear least |
22 |
* squares problem: |
23 |
* minimize 2-norm(| b - A*x |) |
24 |
* using the singular value decomposition (SVD) of A. A is an M-by-N |
25 |
* matrix which may be rank-deficient. |
26 |
* |
27 |
* Several right hand side vectors b and solution vectors x can be |
28 |
* handled in a single call; they are stored as the columns of the |
29 |
* M-by-NRHS right hand side matrix B and the N-by-NRHS solution |
30 |
* matrix X. |
31 |
* |
32 |
* The problem is solved in three steps: |
33 |
* (1) Reduce the coefficient matrix A to bidiagonal form with |
34 |
* Householder transformations, reducing the original problem |
35 |
* into a "bidiagonal least squares problem" (BLS) |
36 |
* (2) Solve the BLS using a divide and conquer approach. |
37 |
* (3) Apply back all the Householder tranformations to solve |
38 |
* the original least squares problem. |
39 |
* |
40 |
* The effective rank of A is determined by treating as zero those |
41 |
* singular values which are less than RCOND times the largest singular |
42 |
* value. |
43 |
* |
44 |
* The divide and conquer algorithm makes very mild assumptions about |
45 |
* floating point arithmetic. It will work on machines with a guard |
46 |
* digit in add/subtract, or on those binary machines without guard |
47 |
* digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or |
48 |
* Cray-2. It could conceivably fail on hexadecimal or decimal machines |
49 |
* without guard digits, but we know of none. |
50 |
* |
51 |
* Arguments |
52 |
* ========= |
53 |
* |
54 |
* M (input) INTEGER |
55 |
* The number of rows of A. M >= 0. |
56 |
* |
57 |
* N (input) INTEGER |
58 |
* The number of columns of A. N >= 0. |
59 |
* |
60 |
* NRHS (input) INTEGER |
61 |
* The number of right hand sides, i.e., the number of columns |
62 |
* of the matrices B and X. NRHS >= 0. |
63 |
* |
64 |
* A (input) DOUBLE PRECISION array, dimension (LDA,N) |
65 |
* On entry, the M-by-N matrix A. |
66 |
* On exit, A has been destroyed. |
67 |
* |
68 |
* LDA (input) INTEGER |
69 |
* The leading dimension of the array A. LDA >= max(1,M). |
70 |
* |
71 |
* B (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS) |
72 |
* On entry, the M-by-NRHS right hand side matrix B. |
73 |
* On exit, B is overwritten by the N-by-NRHS solution |
74 |
* matrix X. If m >= n and RANK = n, the residual |
75 |
* sum-of-squares for the solution in the i-th column is given |
76 |
* by the sum of squares of elements n+1:m in that column. |
77 |
* |
78 |
* LDB (input) INTEGER |
79 |
* The leading dimension of the array B. LDB >= max(1,max(M,N)). |
80 |
* |
81 |
* S (output) DOUBLE PRECISION array, dimension (min(M,N)) |
82 |
* The singular values of A in decreasing order. |
83 |
* The condition number of A in the 2-norm = S(1)/S(min(m,n)). |
84 |
* |
85 |
* RCOND (input) DOUBLE PRECISION |
86 |
* RCOND is used to determine the effective rank of A. |
87 |
* Singular values S(i) <= RCOND*S(1) are treated as zero. |
88 |
* If RCOND < 0, machine precision is used instead. |
89 |
* |
90 |
* RANK (output) INTEGER |
91 |
* The effective rank of A, i.e., the number of singular values |
92 |
* which are greater than RCOND*S(1). |
93 |
* |
94 |
* WORK (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK)) |
95 |
* On exit, if INFO = 0, WORK(1) returns the optimal LWORK. |
96 |
* |
97 |
* LWORK (input) INTEGER |
98 |
* The dimension of the array WORK. LWORK must be at least 1. |
99 |
* The exact minimum amount of workspace needed depends on M, |
100 |
* N and NRHS. As long as LWORK is at least |
101 |
* 12*N + 2*N*SMLSIZ + 8*N*NLVL + N*NRHS + (SMLSIZ+1)**2, |
102 |
* if M is greater than or equal to N or |
103 |
* 12*M + 2*M*SMLSIZ + 8*M*NLVL + M*NRHS + (SMLSIZ+1)**2, |
104 |
* if M is less than N, the code will execute correctly. |
105 |
* SMLSIZ is returned by ILAENV and is equal to the maximum |
106 |
* size of the subproblems at the bottom of the computation |
107 |
* tree (usually about 25), and |
108 |
* NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 ) |
109 |
* For good performance, LWORK should generally be larger. |
110 |
* |
111 |
* If LWORK = -1, then a workspace query is assumed; the routine |
112 |
* only calculates the optimal size of the WORK array, returns |
113 |
* this value as the first entry of the WORK array, and no error |
114 |
* message related to LWORK is issued by XERBLA. |
115 |
* |
116 |
* IWORK (workspace) INTEGER array, dimension (MAX(1,LIWORK)) |
117 |
* LIWORK >= max(1, 3 * MINMN * NLVL + 11 * MINMN), |
118 |
* where MINMN = MIN( M,N ). |
119 |
* On exit, if INFO = 0, IWORK(1) returns the minimum LIWORK. |
120 |
* |
121 |
* INFO (output) INTEGER |
122 |
* = 0: successful exit |
123 |
* < 0: if INFO = -i, the i-th argument had an illegal value. |
124 |
* > 0: the algorithm for computing the SVD failed to converge; |
125 |
* if INFO = i, i off-diagonal elements of an intermediate |
126 |
* bidiagonal form did not converge to zero. |
127 |
* |
128 |
* Further Details |
129 |
* =============== |
130 |
* |
131 |
* Based on contributions by |
132 |
* Ming Gu and Ren-Cang Li, Computer Science Division, University of |
133 |
* California at Berkeley, USA |
134 |
* Osni Marques, LBNL/NERSC, USA |
135 |
* |
136 |
* ===================================================================== |
137 |
* |
138 |
* .. Parameters .. |
139 |
DOUBLE PRECISION ZERO, ONE, TWO |
140 |
PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0 ) |
141 |
* .. |
142 |
* .. Local Scalars .. |
143 |
LOGICAL LQUERY |
144 |
INTEGER IASCL, IBSCL, IE, IL, ITAU, ITAUP, ITAUQ, |
145 |
$ LDWORK, LIWORK, MAXMN, MAXWRK, MINMN, MINWRK, |
146 |
$ MM, MNTHR, NLVL, NWORK, SMLSIZ, WLALSD |
147 |
DOUBLE PRECISION ANRM, BIGNUM, BNRM, EPS, SFMIN, SMLNUM |
148 |
* .. |
149 |
* .. External Subroutines .. |
150 |
EXTERNAL DGEBRD, DGELQF, DGEQRF, DLABAD, DLACPY, DLALSD, |
151 |
$ DLASCL, DLASET, DORMBR, DORMLQ, DORMQR, XERBLA |
152 |
* .. |
153 |
* .. External Functions .. |
154 |
INTEGER ILAENV |
155 |
DOUBLE PRECISION DLAMCH, DLANGE |
156 |
EXTERNAL ILAENV, DLAMCH, DLANGE |
157 |
* .. |
158 |
* .. Intrinsic Functions .. |
159 |
INTRINSIC DBLE, INT, LOG, MAX, MIN |
160 |
* .. |
161 |
* .. Executable Statements .. |
162 |
* |
163 |
* Test the input arguments. |
164 |
* |
165 |
INFO = 0 |
166 |
MINMN = MIN( M, N ) |
167 |
MAXMN = MAX( M, N ) |
168 |
MNTHR = ILAENV( 6, 'DGELSD', ' ', M, N, NRHS, -1 ) |
169 |
LQUERY = ( LWORK.EQ.-1 ) |
170 |
IF( M.LT.0 ) THEN |
171 |
INFO = -1 |
172 |
ELSE IF( N.LT.0 ) THEN |
173 |
INFO = -2 |
174 |
ELSE IF( NRHS.LT.0 ) THEN |
175 |
INFO = -3 |
176 |
ELSE IF( LDA.LT.MAX( 1, M ) ) THEN |
177 |
INFO = -5 |
178 |
ELSE IF( LDB.LT.MAX( 1, MAXMN ) ) THEN |
179 |
INFO = -7 |
180 |
END IF |
181 |
* |
182 |
SMLSIZ = ILAENV( 9, 'DGELSD', ' ', 0, 0, 0, 0 ) |
183 |
* |
184 |
* Compute workspace. |
185 |
* (Note: Comments in the code beginning "Workspace:" describe the |
186 |
* minimal amount of workspace needed at that point in the code, |
187 |
* as well as the preferred amount for good performance. |
188 |
* NB refers to the optimal block size for the immediately |
189 |
* following subroutine, as returned by ILAENV.) |
190 |
* |
191 |
MINWRK = 1 |
192 |
LIWORK = 1 |
193 |
MINMN = MAX( 1, MINMN ) |
194 |
NLVL = MAX( INT( LOG( DBLE( MINMN ) / DBLE( SMLSIZ+1 ) ) / |
195 |
$ LOG( TWO ) ) + 1, 0 ) |
196 |
* |
197 |
IF( INFO.EQ.0 ) THEN |
198 |
MAXWRK = 0 |
199 |
LIWORK = 3*MINMN*NLVL + 11*MINMN |
200 |
MM = M |
201 |
IF( M.GE.N .AND. M.GE.MNTHR ) THEN |
202 |
* |
203 |
* Path 1a - overdetermined, with many more rows than columns. |
204 |
* |
205 |
MM = N |
206 |
MAXWRK = MAX( MAXWRK, N+N*ILAENV( 1, 'DGEQRF', ' ', M, N, |
207 |
$ -1, -1 ) ) |
208 |
MAXWRK = MAX( MAXWRK, N+NRHS* |
209 |
$ ILAENV( 1, 'DORMQR', 'LT', M, NRHS, N, -1 ) ) |
210 |
END IF |
211 |
IF( M.GE.N ) THEN |
212 |
* |
213 |
* Path 1 - overdetermined or exactly determined. |
214 |
* |
215 |
MAXWRK = MAX( MAXWRK, 3*N+( MM+N )* |
216 |
$ ILAENV( 1, 'DGEBRD', ' ', MM, N, -1, -1 ) ) |
217 |
MAXWRK = MAX( MAXWRK, 3*N+NRHS* |
218 |
$ ILAENV( 1, 'DORMBR', 'QLT', MM, NRHS, N, -1 ) ) |
219 |
MAXWRK = MAX( MAXWRK, 3*N+( N-1 )* |
220 |
$ ILAENV( 1, 'DORMBR', 'PLN', N, NRHS, N, -1 ) ) |
221 |
WLALSD = 9*N+2*N*SMLSIZ+8*N*NLVL+N*NRHS+(SMLSIZ+1)**2 |
222 |
MAXWRK = MAX( MAXWRK, 3*N+WLALSD ) |
223 |
MINWRK = MAX( 3*N+MM, 3*N+NRHS, 3*N+WLALSD ) |
224 |
END IF |
225 |
IF( N.GT.M ) THEN |
226 |
WLALSD = 9*M+2*M*SMLSIZ+8*M*NLVL+M*NRHS+(SMLSIZ+1)**2 |
227 |
IF( N.GE.MNTHR ) THEN |
228 |
* |
229 |
* Path 2a - underdetermined, with many more columns |
230 |
* than rows. |
231 |
* |
232 |
MAXWRK = M + M*ILAENV( 1, 'DGELQF', ' ', M, N, -1, -1 ) |
233 |
MAXWRK = MAX( MAXWRK, M*M+4*M+2*M* |
234 |
$ ILAENV( 1, 'DGEBRD', ' ', M, M, -1, -1 ) ) |
235 |
MAXWRK = MAX( MAXWRK, M*M+4*M+NRHS* |
236 |
$ ILAENV( 1, 'DORMBR', 'QLT', M, NRHS, M, -1 ) ) |
237 |
MAXWRK = MAX( MAXWRK, M*M+4*M+( M-1 )* |
238 |
$ ILAENV( 1, 'DORMBR', 'PLN', M, NRHS, M, -1 ) ) |
239 |
IF( NRHS.GT.1 ) THEN |
240 |
MAXWRK = MAX( MAXWRK, M*M+M+M*NRHS ) |
241 |
ELSE |
242 |
MAXWRK = MAX( MAXWRK, M*M+2*M ) |
243 |
END IF |
244 |
MAXWRK = MAX( MAXWRK, M+NRHS* |
245 |
$ ILAENV( 1, 'DORMLQ', 'LT', N, NRHS, M, -1 ) ) |
246 |
MAXWRK = MAX( MAXWRK, M*M+4*M+WLALSD ) |
247 |
! XXX: Ensure the Path 2a case below is triggered. The workspace |
248 |
! calculation should use queries for all routines eventually. |
249 |
MAXWRK = MAX( MAXWRK, |
250 |
$ 4*M+M*M+MAX( M, 2*M-4, NRHS, N-3*M ) ) |
251 |
ELSE |
252 |
* |
253 |
* Path 2 - remaining underdetermined cases. |
254 |
* |
255 |
MAXWRK = 3*M + ( N+M )*ILAENV( 1, 'DGEBRD', ' ', M, N, |
256 |
$ -1, -1 ) |
257 |
MAXWRK = MAX( MAXWRK, 3*M+NRHS* |
258 |
$ ILAENV( 1, 'DORMBR', 'QLT', M, NRHS, N, -1 ) ) |
259 |
MAXWRK = MAX( MAXWRK, 3*M+M* |
260 |
$ ILAENV( 1, 'DORMBR', 'PLN', N, NRHS, M, -1 ) ) |
261 |
MAXWRK = MAX( MAXWRK, 3*M+WLALSD ) |
262 |
END IF |
263 |
MINWRK = MAX( 3*M+NRHS, 3*M+M, 3*M+WLALSD ) |
264 |
END IF |
265 |
MINWRK = MIN( MINWRK, MAXWRK ) |
266 |
WORK( 1 ) = MAXWRK |
267 |
IWORK( 1 ) = LIWORK |
268 |
|
269 |
IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN |
270 |
INFO = -12 |
271 |
END IF |
272 |
END IF |
273 |
* |
274 |
IF( INFO.NE.0 ) THEN |
275 |
CALL XERBLA( 'DGELSD', -INFO ) |
276 |
RETURN |
277 |
ELSE IF( LQUERY ) THEN |
278 |
GO TO 10 |
279 |
END IF |
280 |
* |
281 |
* Quick return if possible. |
282 |
* |
283 |
IF( M.EQ.0 .OR. N.EQ.0 ) THEN |
284 |
RANK = 0 |
285 |
RETURN |
286 |
END IF |
287 |
* |
288 |
* Get machine parameters. |
289 |
* |
290 |
EPS = DLAMCH( 'P' ) |
291 |
SFMIN = DLAMCH( 'S' ) |
292 |
SMLNUM = SFMIN / EPS |
293 |
BIGNUM = ONE / SMLNUM |
294 |
CALL DLABAD( SMLNUM, BIGNUM ) |
295 |
* |
296 |
* Scale A if max entry outside range [SMLNUM,BIGNUM]. |
297 |
* |
298 |
ANRM = DLANGE( 'M', M, N, A, LDA, WORK ) |
299 |
IASCL = 0 |
300 |
IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN |
301 |
* |
302 |
* Scale matrix norm up to SMLNUM. |
303 |
* |
304 |
CALL DLASCL( 'G', 0, 0, ANRM, SMLNUM, M, N, A, LDA, INFO ) |
305 |
IASCL = 1 |
306 |
ELSE IF( ANRM.GT.BIGNUM ) THEN |
307 |
* |
308 |
* Scale matrix norm down to BIGNUM. |
309 |
* |
310 |
CALL DLASCL( 'G', 0, 0, ANRM, BIGNUM, M, N, A, LDA, INFO ) |
311 |
IASCL = 2 |
312 |
ELSE IF( ANRM.EQ.ZERO ) THEN |
313 |
* |
314 |
* Matrix all zero. Return zero solution. |
315 |
* |
316 |
CALL DLASET( 'F', MAX( M, N ), NRHS, ZERO, ZERO, B, LDB ) |
317 |
CALL DLASET( 'F', MINMN, 1, ZERO, ZERO, S, 1 ) |
318 |
RANK = 0 |
319 |
GO TO 10 |
320 |
END IF |
321 |
* |
322 |
* Scale B if max entry outside range [SMLNUM,BIGNUM]. |
323 |
* |
324 |
BNRM = DLANGE( 'M', M, NRHS, B, LDB, WORK ) |
325 |
IBSCL = 0 |
326 |
IF( BNRM.GT.ZERO .AND. BNRM.LT.SMLNUM ) THEN |
327 |
* |
328 |
* Scale matrix norm up to SMLNUM. |
329 |
* |
330 |
CALL DLASCL( 'G', 0, 0, BNRM, SMLNUM, M, NRHS, B, LDB, INFO ) |
331 |
IBSCL = 1 |
332 |
ELSE IF( BNRM.GT.BIGNUM ) THEN |
333 |
* |
334 |
* Scale matrix norm down to BIGNUM. |
335 |
* |
336 |
CALL DLASCL( 'G', 0, 0, BNRM, BIGNUM, M, NRHS, B, LDB, INFO ) |
337 |
IBSCL = 2 |
338 |
END IF |
339 |
* |
340 |
* If M < N make sure certain entries of B are zero. |
341 |
* |
342 |
IF( M.LT.N ) |
343 |
$ CALL DLASET( 'F', N-M, NRHS, ZERO, ZERO, B( M+1, 1 ), LDB ) |
344 |
* |
345 |
* Overdetermined case. |
346 |
* |
347 |
IF( M.GE.N ) THEN |
348 |
* |
349 |
* Path 1 - overdetermined or exactly determined. |
350 |
* |
351 |
MM = M |
352 |
IF( M.GE.MNTHR ) THEN |
353 |
* |
354 |
* Path 1a - overdetermined, with many more rows than columns. |
355 |
* |
356 |
MM = N |
357 |
ITAU = 1 |
358 |
NWORK = ITAU + N |
359 |
* |
360 |
* Compute A=Q*R. |
361 |
* (Workspace: need 2*N, prefer N+N*NB) |
362 |
* |
363 |
CALL DGEQRF( M, N, A, LDA, WORK( ITAU ), WORK( NWORK ), |
364 |
$ LWORK-NWORK+1, INFO ) |
365 |
* |
366 |
* Multiply B by transpose(Q). |
367 |
* (Workspace: need N+NRHS, prefer N+NRHS*NB) |
368 |
* |
369 |
CALL DORMQR( 'L', 'T', M, NRHS, N, A, LDA, WORK( ITAU ), B, |
370 |
$ LDB, WORK( NWORK ), LWORK-NWORK+1, INFO ) |
371 |
* |
372 |
* Zero out below R. |
373 |
* |
374 |
IF( N.GT.1 ) THEN |
375 |
CALL DLASET( 'L', N-1, N-1, ZERO, ZERO, A( 2, 1 ), LDA ) |
376 |
END IF |
377 |
END IF |
378 |
* |
379 |
IE = 1 |
380 |
ITAUQ = IE + N |
381 |
ITAUP = ITAUQ + N |
382 |
NWORK = ITAUP + N |
383 |
* |
384 |
* Bidiagonalize R in A. |
385 |
* (Workspace: need 3*N+MM, prefer 3*N+(MM+N)*NB) |
386 |
* |
387 |
CALL DGEBRD( MM, N, A, LDA, S, WORK( IE ), WORK( ITAUQ ), |
388 |
$ WORK( ITAUP ), WORK( NWORK ), LWORK-NWORK+1, |
389 |
$ INFO ) |
390 |
* |
391 |
* Multiply B by transpose of left bidiagonalizing vectors of R. |
392 |
* (Workspace: need 3*N+NRHS, prefer 3*N+NRHS*NB) |
393 |
* |
394 |
CALL DORMBR( 'Q', 'L', 'T', MM, NRHS, N, A, LDA, WORK( ITAUQ ), |
395 |
$ B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO ) |
396 |
* |
397 |
* Solve the bidiagonal least squares problem. |
398 |
* |
399 |
CALL DLALSD( 'U', SMLSIZ, N, NRHS, S, WORK( IE ), B, LDB, |
400 |
$ RCOND, RANK, WORK( NWORK ), IWORK, INFO ) |
401 |
IF( INFO.NE.0 ) THEN |
402 |
GO TO 10 |
403 |
END IF |
404 |
* |
405 |
* Multiply B by right bidiagonalizing vectors of R. |
406 |
* |
407 |
CALL DORMBR( 'P', 'L', 'N', N, NRHS, N, A, LDA, WORK( ITAUP ), |
408 |
$ B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO ) |
409 |
* |
410 |
ELSE IF( N.GE.MNTHR .AND. LWORK.GE.4*M+M*M+ |
411 |
$ MAX( M, 2*M-4, NRHS, N-3*M, WLALSD ) ) THEN |
412 |
* |
413 |
* Path 2a - underdetermined, with many more columns than rows |
414 |
* and sufficient workspace for an efficient algorithm. |
415 |
* |
416 |
LDWORK = M |
417 |
IF( LWORK.GE.MAX( 4*M+M*LDA+MAX( M, 2*M-4, NRHS, N-3*M ), |
418 |
$ M*LDA+M+M*NRHS, 4*M+M*LDA+WLALSD ) )LDWORK = LDA |
419 |
ITAU = 1 |
420 |
NWORK = M + 1 |
421 |
* |
422 |
* Compute A=L*Q. |
423 |
* (Workspace: need 2*M, prefer M+M*NB) |
424 |
* |
425 |
CALL DGELQF( M, N, A, LDA, WORK( ITAU ), WORK( NWORK ), |
426 |
$ LWORK-NWORK+1, INFO ) |
427 |
IL = NWORK |
428 |
* |
429 |
* Copy L to WORK(IL), zeroing out above its diagonal. |
430 |
* |
431 |
CALL DLACPY( 'L', M, M, A, LDA, WORK( IL ), LDWORK ) |
432 |
CALL DLASET( 'U', M-1, M-1, ZERO, ZERO, WORK( IL+LDWORK ), |
433 |
$ LDWORK ) |
434 |
IE = IL + LDWORK*M |
435 |
ITAUQ = IE + M |
436 |
ITAUP = ITAUQ + M |
437 |
NWORK = ITAUP + M |
438 |
* |
439 |
* Bidiagonalize L in WORK(IL). |
440 |
* (Workspace: need M*M+5*M, prefer M*M+4*M+2*M*NB) |
441 |
* |
442 |
CALL DGEBRD( M, M, WORK( IL ), LDWORK, S, WORK( IE ), |
443 |
$ WORK( ITAUQ ), WORK( ITAUP ), WORK( NWORK ), |
444 |
$ LWORK-NWORK+1, INFO ) |
445 |
* |
446 |
* Multiply B by transpose of left bidiagonalizing vectors of L. |
447 |
* (Workspace: need M*M+4*M+NRHS, prefer M*M+4*M+NRHS*NB) |
448 |
* |
449 |
CALL DORMBR( 'Q', 'L', 'T', M, NRHS, M, WORK( IL ), LDWORK, |
450 |
$ WORK( ITAUQ ), B, LDB, WORK( NWORK ), |
451 |
$ LWORK-NWORK+1, INFO ) |
452 |
* |
453 |
* Solve the bidiagonal least squares problem. |
454 |
* |
455 |
CALL DLALSD( 'U', SMLSIZ, M, NRHS, S, WORK( IE ), B, LDB, |
456 |
$ RCOND, RANK, WORK( NWORK ), IWORK, INFO ) |
457 |
IF( INFO.NE.0 ) THEN |
458 |
GO TO 10 |
459 |
END IF |
460 |
* |
461 |
* Multiply B by right bidiagonalizing vectors of L. |
462 |
* |
463 |
CALL DORMBR( 'P', 'L', 'N', M, NRHS, M, WORK( IL ), LDWORK, |
464 |
$ WORK( ITAUP ), B, LDB, WORK( NWORK ), |
465 |
$ LWORK-NWORK+1, INFO ) |
466 |
* |
467 |
* Zero out below first M rows of B. |
468 |
* |
469 |
CALL DLASET( 'F', N-M, NRHS, ZERO, ZERO, B( M+1, 1 ), LDB ) |
470 |
NWORK = ITAU + M |
471 |
* |
472 |
* Multiply transpose(Q) by B. |
473 |
* (Workspace: need M+NRHS, prefer M+NRHS*NB) |
474 |
* |
475 |
CALL DORMLQ( 'L', 'T', N, NRHS, M, A, LDA, WORK( ITAU ), B, |
476 |
$ LDB, WORK( NWORK ), LWORK-NWORK+1, INFO ) |
477 |
* |
478 |
ELSE |
479 |
* |
480 |
* Path 2 - remaining underdetermined cases. |
481 |
* |
482 |
IE = 1 |
483 |
ITAUQ = IE + M |
484 |
ITAUP = ITAUQ + M |
485 |
NWORK = ITAUP + M |
486 |
* |
487 |
* Bidiagonalize A. |
488 |
* (Workspace: need 3*M+N, prefer 3*M+(M+N)*NB) |
489 |
* |
490 |
CALL DGEBRD( M, N, A, LDA, S, WORK( IE ), WORK( ITAUQ ), |
491 |
$ WORK( ITAUP ), WORK( NWORK ), LWORK-NWORK+1, |
492 |
$ INFO ) |
493 |
* |
494 |
* Multiply B by transpose of left bidiagonalizing vectors. |
495 |
* (Workspace: need 3*M+NRHS, prefer 3*M+NRHS*NB) |
496 |
* |
497 |
CALL DORMBR( 'Q', 'L', 'T', M, NRHS, N, A, LDA, WORK( ITAUQ ), |
498 |
$ B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO ) |
499 |
* |
500 |
* Solve the bidiagonal least squares problem. |
501 |
* |
502 |
CALL DLALSD( 'L', SMLSIZ, M, NRHS, S, WORK( IE ), B, LDB, |
503 |
$ RCOND, RANK, WORK( NWORK ), IWORK, INFO ) |
504 |
IF( INFO.NE.0 ) THEN |
505 |
GO TO 10 |
506 |
END IF |
507 |
* |
508 |
* Multiply B by right bidiagonalizing vectors of A. |
509 |
* |
510 |
CALL DORMBR( 'P', 'L', 'N', N, NRHS, M, A, LDA, WORK( ITAUP ), |
511 |
$ B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO ) |
512 |
* |
513 |
END IF |
514 |
* |
515 |
* Undo scaling. |
516 |
* |
517 |
IF( IASCL.EQ.1 ) THEN |
518 |
CALL DLASCL( 'G', 0, 0, ANRM, SMLNUM, N, NRHS, B, LDB, INFO ) |
519 |
CALL DLASCL( 'G', 0, 0, SMLNUM, ANRM, MINMN, 1, S, MINMN, |
520 |
$ INFO ) |
521 |
ELSE IF( IASCL.EQ.2 ) THEN |
522 |
CALL DLASCL( 'G', 0, 0, ANRM, BIGNUM, N, NRHS, B, LDB, INFO ) |
523 |
CALL DLASCL( 'G', 0, 0, BIGNUM, ANRM, MINMN, 1, S, MINMN, |
524 |
$ INFO ) |
525 |
END IF |
526 |
IF( IBSCL.EQ.1 ) THEN |
527 |
CALL DLASCL( 'G', 0, 0, SMLNUM, BNRM, N, NRHS, B, LDB, INFO ) |
528 |
ELSE IF( IBSCL.EQ.2 ) THEN |
529 |
CALL DLASCL( 'G', 0, 0, BIGNUM, BNRM, N, NRHS, B, LDB, INFO ) |
530 |
END IF |
531 |
* |
532 |
10 CONTINUE |
533 |
WORK( 1 ) = MAXWRK |
534 |
IWORK( 1 ) = LIWORK |
535 |
RETURN |
536 |
* |
537 |
* End of DGELSD |
538 |
* |
539 |
END |