001:       SUBROUTINE ZGELSD( M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK,
002:      $                   WORK, LWORK, RWORK, IWORK, INFO )
003: *
004: *  -- LAPACK driver routine (version 3.2) --
005: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            INFO, LDA, LDB, LWORK, M, N, NRHS, RANK
010:       DOUBLE PRECISION   RCOND
011: *     ..
012: *     .. Array Arguments ..
013:       INTEGER            IWORK( * )
014:       DOUBLE PRECISION   RWORK( * ), S( * )
015:       COMPLEX*16         A( LDA, * ), B( LDB, * ), WORK( * )
016: *     ..
017: *
018: *  Purpose
019: *  =======
020: *
021: *  ZGELSD computes the minimum-norm solution to a real linear least
022: *  squares problem:
023: *      minimize 2-norm(| b - A*x |)
024: *  using the singular value decomposition (SVD) of A. A is an M-by-N
025: *  matrix which may be rank-deficient.
026: *
027: *  Several right hand side vectors b and solution vectors x can be
028: *  handled in a single call; they are stored as the columns of the
029: *  M-by-NRHS right hand side matrix B and the N-by-NRHS solution
030: *  matrix X.
031: *
032: *  The problem is solved in three steps:
033: *  (1) Reduce the coefficient matrix A to bidiagonal form with
034: *      Householder tranformations, reducing the original problem
035: *      into a "bidiagonal least squares problem" (BLS)
036: *  (2) Solve the BLS using a divide and conquer approach.
037: *  (3) Apply back all the Householder tranformations to solve
038: *      the original least squares problem.
039: *
040: *  The effective rank of A is determined by treating as zero those
041: *  singular values which are less than RCOND times the largest singular
042: *  value.
043: *
044: *  The divide and conquer algorithm makes very mild assumptions about
045: *  floating point arithmetic. It will work on machines with a guard
046: *  digit in add/subtract, or on those binary machines without guard
047: *  digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or
048: *  Cray-2. It could conceivably fail on hexadecimal or decimal machines
049: *  without guard digits, but we know of none.
050: *
051: *  Arguments
052: *  =========
053: *
054: *  M       (input) INTEGER
055: *          The number of rows of the matrix A. M >= 0.
056: *
057: *  N       (input) INTEGER
058: *          The number of columns of the matrix A. N >= 0.
059: *
060: *  NRHS    (input) INTEGER
061: *          The number of right hand sides, i.e., the number of columns
062: *          of the matrices B and X. NRHS >= 0.
063: *
064: *  A       (input) COMPLEX*16 array, dimension (LDA,N)
065: *          On entry, the M-by-N matrix A.
066: *          On exit, A has been destroyed.
067: *
068: *  LDA     (input) INTEGER
069: *          The leading dimension of the array A. LDA >= max(1,M).
070: *
071: *  B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
072: *          On entry, the M-by-NRHS right hand side matrix B.
073: *          On exit, B is overwritten by the N-by-NRHS solution matrix X.
074: *          If m >= n and RANK = n, the residual sum-of-squares for
075: *          the solution in the i-th column is given by the sum of
076: *          squares of the modulus of elements n+1:m in that column.
077: *
078: *  LDB     (input) INTEGER
079: *          The leading dimension of the array B.  LDB >= max(1,M,N).
080: *
081: *  S       (output) DOUBLE PRECISION array, dimension (min(M,N))
082: *          The singular values of A in decreasing order.
083: *          The condition number of A in the 2-norm = S(1)/S(min(m,n)).
084: *
085: *  RCOND   (input) DOUBLE PRECISION
086: *          RCOND is used to determine the effective rank of A.
087: *          Singular values S(i) <= RCOND*S(1) are treated as zero.
088: *          If RCOND < 0, machine precision is used instead.
089: *
090: *  RANK    (output) INTEGER
091: *          The effective rank of A, i.e., the number of singular values
092: *          which are greater than RCOND*S(1).
093: *
094: *  WORK    (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
095: *          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
096: *
097: *  LWORK   (input) INTEGER
098: *          The dimension of the array WORK. LWORK must be at least 1.
099: *          The exact minimum amount of workspace needed depends on M,
100: *          N and NRHS. As long as LWORK is at least
101: *              2*N + N*NRHS
102: *          if M is greater than or equal to N or
103: *              2*M + M*NRHS
104: *          if M is less than N, the code will execute correctly.
105: *          For good performance, LWORK should generally be larger.
106: *
107: *          If LWORK = -1, then a workspace query is assumed; the routine
108: *          only calculates the optimal size of the array WORK and the
109: *          minimum sizes of the arrays RWORK and IWORK, and returns
110: *          these values as the first entries of the WORK, RWORK and
111: *          IWORK arrays, and no error message related to LWORK is issued
112: *          by XERBLA.
113: *
114: *  RWORK   (workspace) DOUBLE PRECISION array, dimension (MAX(1,LRWORK))
115: *          LRWORK >=
116: *              10*N + 2*N*SMLSIZ + 8*N*NLVL + 3*SMLSIZ*NRHS +
117: *             (SMLSIZ+1)**2
118: *          if M is greater than or equal to N or
119: *             10*M + 2*M*SMLSIZ + 8*M*NLVL + 3*SMLSIZ*NRHS +
120: *             (SMLSIZ+1)**2
121: *          if M is less than N, the code will execute correctly.
122: *          SMLSIZ is returned by ILAENV and is equal to the maximum
123: *          size of the subproblems at the bottom of the computation
124: *          tree (usually about 25), and
125: *             NLVL = MAX( 0, INT( LOG_2( MIN( M,N )/(SMLSIZ+1) ) ) + 1 )
126: *          On exit, if INFO = 0, RWORK(1) returns the minimum LRWORK.
127: *
128: *  IWORK   (workspace) INTEGER array, dimension (MAX(1,LIWORK))
129: *          LIWORK >= max(1, 3*MINMN*NLVL + 11*MINMN),
130: *          where MINMN = MIN( M,N ).
131: *          On exit, if INFO = 0, IWORK(1) returns the minimum LIWORK.
132: *
133: *  INFO    (output) INTEGER
134: *          = 0: successful exit
135: *          < 0: if INFO = -i, the i-th argument had an illegal value.
136: *          > 0:  the algorithm for computing the SVD failed to converge;
137: *                if INFO = i, i off-diagonal elements of an intermediate
138: *                bidiagonal form did not converge to zero.
139: *
140: *  Further Details
141: *  ===============
142: *
143: *  Based on contributions by
144: *     Ming Gu and Ren-Cang Li, Computer Science Division, University of
145: *       California at Berkeley, USA
146: *     Osni Marques, LBNL/NERSC, USA
147: *
148: *  =====================================================================
149: *
150: *     .. Parameters ..
151:       DOUBLE PRECISION   ZERO, ONE, TWO
152:       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0 )
153:       COMPLEX*16         CZERO
154:       PARAMETER          ( CZERO = ( 0.0D+0, 0.0D+0 ) )
155: *     ..
156: *     .. Local Scalars ..
157:       LOGICAL            LQUERY
158:       INTEGER            IASCL, IBSCL, IE, IL, ITAU, ITAUP, ITAUQ,
159:      $                   LDWORK, LIWORK, LRWORK, MAXMN, MAXWRK, MINMN,
160:      $                   MINWRK, MM, MNTHR, NLVL, NRWORK, NWORK, SMLSIZ
161:       DOUBLE PRECISION   ANRM, BIGNUM, BNRM, EPS, SFMIN, SMLNUM
162: *     ..
163: *     .. External Subroutines ..
164:       EXTERNAL           DLABAD, DLASCL, DLASET, XERBLA, ZGEBRD, ZGELQF,
165:      $                   ZGEQRF, ZLACPY, ZLALSD, ZLASCL, ZLASET, ZUNMBR,
166:      $                   ZUNMLQ, ZUNMQR
167: *     ..
168: *     .. External Functions ..
169:       INTEGER            ILAENV
170:       DOUBLE PRECISION   DLAMCH, ZLANGE
171:       EXTERNAL           ILAENV, DLAMCH, ZLANGE
172: *     ..
173: *     .. Intrinsic Functions ..
174:       INTRINSIC          INT, LOG, MAX, MIN, DBLE
175: *     ..
176: *     .. Executable Statements ..
177: *
178: *     Test the input arguments.
179: *
180:       INFO = 0
181:       MINMN = MIN( M, N )
182:       MAXMN = MAX( M, N )
183:       LQUERY = ( LWORK.EQ.-1 )
184:       IF( M.LT.0 ) THEN
185:          INFO = -1
186:       ELSE IF( N.LT.0 ) THEN
187:          INFO = -2
188:       ELSE IF( NRHS.LT.0 ) THEN
189:          INFO = -3
190:       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
191:          INFO = -5
192:       ELSE IF( LDB.LT.MAX( 1, MAXMN ) ) THEN
193:          INFO = -7
194:       END IF
195: *
196: *     Compute workspace.
197: *     (Note: Comments in the code beginning "Workspace:" describe the
198: *     minimal amount of workspace needed at that point in the code,
199: *     as well as the preferred amount for good performance.
200: *     NB refers to the optimal block size for the immediately
201: *     following subroutine, as returned by ILAENV.)
202: *
203:       IF( INFO.EQ.0 ) THEN
204:          MINWRK = 1
205:          MAXWRK = 1
206:          LIWORK = 1
207:          LRWORK = 1
208:          IF( MINMN.GT.0 ) THEN
209:             SMLSIZ = ILAENV( 9, 'ZGELSD', ' ', 0, 0, 0, 0 )
210:             MNTHR = ILAENV( 6, 'ZGELSD', ' ', M, N, NRHS, -1 )
211:             NLVL = MAX( INT( LOG( DBLE( MINMN ) / DBLE( SMLSIZ + 1 ) ) /
212:      $                  LOG( TWO ) ) + 1, 0 )
213:             LIWORK = 3*MINMN*NLVL + 11*MINMN
214:             MM = M
215:             IF( M.GE.N .AND. M.GE.MNTHR ) THEN
216: *
217: *              Path 1a - overdetermined, with many more rows than
218: *                        columns.
219: *
220:                MM = N
221:                MAXWRK = MAX( MAXWRK, N*ILAENV( 1, 'ZGEQRF', ' ', M, N,
222:      $                       -1, -1 ) )
223:                MAXWRK = MAX( MAXWRK, NRHS*ILAENV( 1, 'ZUNMQR', 'LC', M,
224:      $                       NRHS, N, -1 ) )
225:             END IF
226:             IF( M.GE.N ) THEN
227: *
228: *              Path 1 - overdetermined or exactly determined.
229: *
230:                LRWORK = 10*N + 2*N*SMLSIZ + 8*N*NLVL + 3*SMLSIZ*NRHS +
231:      $                  ( SMLSIZ + 1 )**2
232:                MAXWRK = MAX( MAXWRK, 2*N + ( MM + N )*ILAENV( 1,
233:      $                       'ZGEBRD', ' ', MM, N, -1, -1 ) )
234:                MAXWRK = MAX( MAXWRK, 2*N + NRHS*ILAENV( 1, 'ZUNMBR',
235:      $                       'QLC', MM, NRHS, N, -1 ) )
236:                MAXWRK = MAX( MAXWRK, 2*N + ( N - 1 )*ILAENV( 1,
237:      $                       'ZUNMBR', 'PLN', N, NRHS, N, -1 ) )
238:                MAXWRK = MAX( MAXWRK, 2*N + N*NRHS )
239:                MINWRK = MAX( 2*N + MM, 2*N + N*NRHS )
240:             END IF
241:             IF( N.GT.M ) THEN
242:                LRWORK = 10*M + 2*M*SMLSIZ + 8*M*NLVL + 3*SMLSIZ*NRHS +
243:      $                  ( SMLSIZ + 1 )**2
244:                IF( N.GE.MNTHR ) THEN
245: *
246: *                 Path 2a - underdetermined, with many more columns
247: *                           than rows.
248: *
249:                   MAXWRK = M + M*ILAENV( 1, 'ZGELQF', ' ', M, N, -1,
250:      $                     -1 )
251:                   MAXWRK = MAX( MAXWRK, M*M + 4*M + 2*M*ILAENV( 1,
252:      $                          'ZGEBRD', ' ', M, M, -1, -1 ) )
253:                   MAXWRK = MAX( MAXWRK, M*M + 4*M + NRHS*ILAENV( 1,
254:      $                          'ZUNMBR', 'QLC', M, NRHS, M, -1 ) )
255:                   MAXWRK = MAX( MAXWRK, M*M + 4*M + ( M - 1 )*ILAENV( 1,
256:      $                          'ZUNMLQ', 'LC', N, NRHS, M, -1 ) )
257:                   IF( NRHS.GT.1 ) THEN
258:                      MAXWRK = MAX( MAXWRK, M*M + M + M*NRHS )
259:                   ELSE
260:                      MAXWRK = MAX( MAXWRK, M*M + 2*M )
261:                   END IF
262:                   MAXWRK = MAX( MAXWRK, M*M + 4*M + M*NRHS )
263: !     XXX: Ensure the Path 2a case below is triggered.  The workspace
264: !     calculation should use queries for all routines eventually.
265:                   MAXWRK = MAX( MAXWRK,
266:      $                 4*M+M*M+MAX( M, 2*M-4, NRHS, N-3*M ) )
267:                ELSE
268: *
269: *                 Path 2 - underdetermined.
270: *
271:                   MAXWRK = 2*M + ( N + M )*ILAENV( 1, 'ZGEBRD', ' ', M,
272:      $                     N, -1, -1 )
273:                   MAXWRK = MAX( MAXWRK, 2*M + NRHS*ILAENV( 1, 'ZUNMBR',
274:      $                          'QLC', M, NRHS, M, -1 ) )
275:                   MAXWRK = MAX( MAXWRK, 2*M + M*ILAENV( 1, 'ZUNMBR',
276:      $                          'PLN', N, NRHS, M, -1 ) )
277:                   MAXWRK = MAX( MAXWRK, 2*M + M*NRHS )
278:                END IF
279:                MINWRK = MAX( 2*M + N, 2*M + M*NRHS )
280:             END IF
281:          END IF
282:          MINWRK = MIN( MINWRK, MAXWRK )
283:          WORK( 1 ) = MAXWRK
284:          IWORK( 1 ) = LIWORK
285:          RWORK( 1 ) = LRWORK
286: *
287:          IF( LWORK.LT.MINWRK .AND. .NOT.LQUERY ) THEN
288:             INFO = -12
289:          END IF
290:       END IF
291: *
292:       IF( INFO.NE.0 ) THEN
293:          CALL XERBLA( 'ZGELSD', -INFO )
294:          RETURN
295:       ELSE IF( LQUERY ) THEN
296:          RETURN
297:       END IF
298: *
299: *     Quick return if possible.
300: *
301:       IF( M.EQ.0 .OR. N.EQ.0 ) THEN
302:          RANK = 0
303:          RETURN
304:       END IF
305: *
306: *     Get machine parameters.
307: *
308:       EPS = DLAMCH( 'P' )
309:       SFMIN = DLAMCH( 'S' )
310:       SMLNUM = SFMIN / EPS
311:       BIGNUM = ONE / SMLNUM
312:       CALL DLABAD( SMLNUM, BIGNUM )
313: *
314: *     Scale A if max entry outside range [SMLNUM,BIGNUM].
315: *
316:       ANRM = ZLANGE( 'M', M, N, A, LDA, RWORK )
317:       IASCL = 0
318:       IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
319: *
320: *        Scale matrix norm up to SMLNUM
321: *
322:          CALL ZLASCL( 'G', 0, 0, ANRM, SMLNUM, M, N, A, LDA, INFO )
323:          IASCL = 1
324:       ELSE IF( ANRM.GT.BIGNUM ) THEN
325: *
326: *        Scale matrix norm down to BIGNUM.
327: *
328:          CALL ZLASCL( 'G', 0, 0, ANRM, BIGNUM, M, N, A, LDA, INFO )
329:          IASCL = 2
330:       ELSE IF( ANRM.EQ.ZERO ) THEN
331: *
332: *        Matrix all zero. Return zero solution.
333: *
334:          CALL ZLASET( 'F', MAX( M, N ), NRHS, CZERO, CZERO, B, LDB )
335:          CALL DLASET( 'F', MINMN, 1, ZERO, ZERO, S, 1 )
336:          RANK = 0
337:          GO TO 10
338:       END IF
339: *
340: *     Scale B if max entry outside range [SMLNUM,BIGNUM].
341: *
342:       BNRM = ZLANGE( 'M', M, NRHS, B, LDB, RWORK )
343:       IBSCL = 0
344:       IF( BNRM.GT.ZERO .AND. BNRM.LT.SMLNUM ) THEN
345: *
346: *        Scale matrix norm up to SMLNUM.
347: *
348:          CALL ZLASCL( 'G', 0, 0, BNRM, SMLNUM, M, NRHS, B, LDB, INFO )
349:          IBSCL = 1
350:       ELSE IF( BNRM.GT.BIGNUM ) THEN
351: *
352: *        Scale matrix norm down to BIGNUM.
353: *
354:          CALL ZLASCL( 'G', 0, 0, BNRM, BIGNUM, M, NRHS, B, LDB, INFO )
355:          IBSCL = 2
356:       END IF
357: *
358: *     If M < N make sure B(M+1:N,:) = 0
359: *
360:       IF( M.LT.N )
361:      $   CALL ZLASET( 'F', N-M, NRHS, CZERO, CZERO, B( M+1, 1 ), LDB )
362: *
363: *     Overdetermined case.
364: *
365:       IF( M.GE.N ) THEN
366: *
367: *        Path 1 - overdetermined or exactly determined.
368: *
369:          MM = M
370:          IF( M.GE.MNTHR ) THEN
371: *
372: *           Path 1a - overdetermined, with many more rows than columns
373: *
374:             MM = N
375:             ITAU = 1
376:             NWORK = ITAU + N
377: *
378: *           Compute A=Q*R.
379: *           (RWorkspace: need N)
380: *           (CWorkspace: need N, prefer N*NB)
381: *
382:             CALL ZGEQRF( M, N, A, LDA, WORK( ITAU ), WORK( NWORK ),
383:      $                   LWORK-NWORK+1, INFO )
384: *
385: *           Multiply B by transpose(Q).
386: *           (RWorkspace: need N)
387: *           (CWorkspace: need NRHS, prefer NRHS*NB)
388: *
389:             CALL ZUNMQR( 'L', 'C', M, NRHS, N, A, LDA, WORK( ITAU ), B,
390:      $                   LDB, WORK( NWORK ), LWORK-NWORK+1, INFO )
391: *
392: *           Zero out below R.
393: *
394:             IF( N.GT.1 ) THEN
395:                CALL ZLASET( 'L', N-1, N-1, CZERO, CZERO, A( 2, 1 ),
396:      $                      LDA )
397:             END IF
398:          END IF
399: *
400:          ITAUQ = 1
401:          ITAUP = ITAUQ + N
402:          NWORK = ITAUP + N
403:          IE = 1
404:          NRWORK = IE + N
405: *
406: *        Bidiagonalize R in A.
407: *        (RWorkspace: need N)
408: *        (CWorkspace: need 2*N+MM, prefer 2*N+(MM+N)*NB)
409: *
410:          CALL ZGEBRD( MM, N, A, LDA, S, RWORK( IE ), WORK( ITAUQ ),
411:      $                WORK( ITAUP ), WORK( NWORK ), LWORK-NWORK+1,
412:      $                INFO )
413: *
414: *        Multiply B by transpose of left bidiagonalizing vectors of R.
415: *        (CWorkspace: need 2*N+NRHS, prefer 2*N+NRHS*NB)
416: *
417:          CALL ZUNMBR( 'Q', 'L', 'C', MM, NRHS, N, A, LDA, WORK( ITAUQ ),
418:      $                B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO )
419: *
420: *        Solve the bidiagonal least squares problem.
421: *
422:          CALL ZLALSD( 'U', SMLSIZ, N, NRHS, S, RWORK( IE ), B, LDB,
423:      $                RCOND, RANK, WORK( NWORK ), RWORK( NRWORK ),
424:      $                IWORK, INFO )
425:          IF( INFO.NE.0 ) THEN
426:             GO TO 10
427:          END IF
428: *
429: *        Multiply B by right bidiagonalizing vectors of R.
430: *
431:          CALL ZUNMBR( 'P', 'L', 'N', N, NRHS, N, A, LDA, WORK( ITAUP ),
432:      $                B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO )
433: *
434:       ELSE IF( N.GE.MNTHR .AND. LWORK.GE.4*M+M*M+
435:      $         MAX( M, 2*M-4, NRHS, N-3*M ) ) THEN
436: *
437: *        Path 2a - underdetermined, with many more columns than rows
438: *        and sufficient workspace for an efficient algorithm.
439: *
440:          LDWORK = M
441:          IF( LWORK.GE.MAX( 4*M+M*LDA+MAX( M, 2*M-4, NRHS, N-3*M ),
442:      $       M*LDA+M+M*NRHS ) )LDWORK = LDA
443:          ITAU = 1
444:          NWORK = M + 1
445: *
446: *        Compute A=L*Q.
447: *        (CWorkspace: need 2*M, prefer M+M*NB)
448: *
449:          CALL ZGELQF( M, N, A, LDA, WORK( ITAU ), WORK( NWORK ),
450:      $                LWORK-NWORK+1, INFO )
451:          IL = NWORK
452: *
453: *        Copy L to WORK(IL), zeroing out above its diagonal.
454: *
455:          CALL ZLACPY( 'L', M, M, A, LDA, WORK( IL ), LDWORK )
456:          CALL ZLASET( 'U', M-1, M-1, CZERO, CZERO, WORK( IL+LDWORK ),
457:      $                LDWORK )
458:          ITAUQ = IL + LDWORK*M
459:          ITAUP = ITAUQ + M
460:          NWORK = ITAUP + M
461:          IE = 1
462:          NRWORK = IE + M
463: *
464: *        Bidiagonalize L in WORK(IL).
465: *        (RWorkspace: need M)
466: *        (CWorkspace: need M*M+4*M, prefer M*M+4*M+2*M*NB)
467: *
468:          CALL ZGEBRD( M, M, WORK( IL ), LDWORK, S, RWORK( IE ),
469:      $                WORK( ITAUQ ), WORK( ITAUP ), WORK( NWORK ),
470:      $                LWORK-NWORK+1, INFO )
471: *
472: *        Multiply B by transpose of left bidiagonalizing vectors of L.
473: *        (CWorkspace: need M*M+4*M+NRHS, prefer M*M+4*M+NRHS*NB)
474: *
475:          CALL ZUNMBR( 'Q', 'L', 'C', M, NRHS, M, WORK( IL ), LDWORK,
476:      $                WORK( ITAUQ ), B, LDB, WORK( NWORK ),
477:      $                LWORK-NWORK+1, INFO )
478: *
479: *        Solve the bidiagonal least squares problem.
480: *
481:          CALL ZLALSD( 'U', SMLSIZ, M, NRHS, S, RWORK( IE ), B, LDB,
482:      $                RCOND, RANK, WORK( NWORK ), RWORK( NRWORK ),
483:      $                IWORK, INFO )
484:          IF( INFO.NE.0 ) THEN
485:             GO TO 10
486:          END IF
487: *
488: *        Multiply B by right bidiagonalizing vectors of L.
489: *
490:          CALL ZUNMBR( 'P', 'L', 'N', M, NRHS, M, WORK( IL ), LDWORK,
491:      $                WORK( ITAUP ), B, LDB, WORK( NWORK ),
492:      $                LWORK-NWORK+1, INFO )
493: *
494: *        Zero out below first M rows of B.
495: *
496:          CALL ZLASET( 'F', N-M, NRHS, CZERO, CZERO, B( M+1, 1 ), LDB )
497:          NWORK = ITAU + M
498: *
499: *        Multiply transpose(Q) by B.
500: *        (CWorkspace: need NRHS, prefer NRHS*NB)
501: *
502:          CALL ZUNMLQ( 'L', 'C', N, NRHS, M, A, LDA, WORK( ITAU ), B,
503:      $                LDB, WORK( NWORK ), LWORK-NWORK+1, INFO )
504: *
505:       ELSE
506: *
507: *        Path 2 - remaining underdetermined cases.
508: *
509:          ITAUQ = 1
510:          ITAUP = ITAUQ + M
511:          NWORK = ITAUP + M
512:          IE = 1
513:          NRWORK = IE + M
514: *
515: *        Bidiagonalize A.
516: *        (RWorkspace: need M)
517: *        (CWorkspace: need 2*M+N, prefer 2*M+(M+N)*NB)
518: *
519:          CALL ZGEBRD( M, N, A, LDA, S, RWORK( IE ), WORK( ITAUQ ),
520:      $                WORK( ITAUP ), WORK( NWORK ), LWORK-NWORK+1,
521:      $                INFO )
522: *
523: *        Multiply B by transpose of left bidiagonalizing vectors.
524: *        (CWorkspace: need 2*M+NRHS, prefer 2*M+NRHS*NB)
525: *
526:          CALL ZUNMBR( 'Q', 'L', 'C', M, NRHS, N, A, LDA, WORK( ITAUQ ),
527:      $                B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO )
528: *
529: *        Solve the bidiagonal least squares problem.
530: *
531:          CALL ZLALSD( 'L', SMLSIZ, M, NRHS, S, RWORK( IE ), B, LDB,
532:      $                RCOND, RANK, WORK( NWORK ), RWORK( NRWORK ),
533:      $                IWORK, INFO )
534:          IF( INFO.NE.0 ) THEN
535:             GO TO 10
536:          END IF
537: *
538: *        Multiply B by right bidiagonalizing vectors of A.
539: *
540:          CALL ZUNMBR( 'P', 'L', 'N', N, NRHS, M, A, LDA, WORK( ITAUP ),
541:      $                B, LDB, WORK( NWORK ), LWORK-NWORK+1, INFO )
542: *
543:       END IF
544: *
545: *     Undo scaling.
546: *
547:       IF( IASCL.EQ.1 ) THEN
548:          CALL ZLASCL( 'G', 0, 0, ANRM, SMLNUM, N, NRHS, B, LDB, INFO )
549:          CALL DLASCL( 'G', 0, 0, SMLNUM, ANRM, MINMN, 1, S, MINMN,
550:      $                INFO )
551:       ELSE IF( IASCL.EQ.2 ) THEN
552:          CALL ZLASCL( 'G', 0, 0, ANRM, BIGNUM, N, NRHS, B, LDB, INFO )
553:          CALL DLASCL( 'G', 0, 0, BIGNUM, ANRM, MINMN, 1, S, MINMN,
554:      $                INFO )
555:       END IF
556:       IF( IBSCL.EQ.1 ) THEN
557:          CALL ZLASCL( 'G', 0, 0, SMLNUM, BNRM, N, NRHS, B, LDB, INFO )
558:       ELSE IF( IBSCL.EQ.2 ) THEN
559:          CALL ZLASCL( 'G', 0, 0, BIGNUM, BNRM, N, NRHS, B, LDB, INFO )
560:       END IF
561: *
562:    10 CONTINUE
563:       WORK( 1 ) = MAXWRK
564:       IWORK( 1 ) = LIWORK
565:       RWORK( 1 ) = LRWORK
566:       RETURN
567: *
568: *     End of ZGELSD
569: *
570:       END
571: