Statistiques
| Révision :

root / src / lapack / double / dgelsd.f @ 10

Historique | Voir | Annoter | Télécharger (18,5 ko)

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