Statistiques
| Révision :

root / src / lapack / double / dgelsy.f @ 9

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

1 1 pfleura2
      SUBROUTINE DGELSY( M, N, NRHS, A, LDA, B, LDB, JPVT, RCOND, RANK,
2 1 pfleura2
     $                   WORK, LWORK, INFO )
3 1 pfleura2
*
4 1 pfleura2
*  -- LAPACK driver routine (version 3.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
*     November 2006
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            JPVT( * )
15 1 pfleura2
      DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), WORK( * )
16 1 pfleura2
*     ..
17 1 pfleura2
*
18 1 pfleura2
*  Purpose
19 1 pfleura2
*  =======
20 1 pfleura2
*
21 1 pfleura2
*  DGELSY computes the minimum-norm solution to a real linear least
22 1 pfleura2
*  squares problem:
23 1 pfleura2
*      minimize || A * X - B ||
24 1 pfleura2
*  using a complete orthogonal factorization 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 routine first computes a QR factorization with column pivoting:
33 1 pfleura2
*      A * P = Q * [ R11 R12 ]
34 1 pfleura2
*                  [  0  R22 ]
35 1 pfleura2
*  with R11 defined as the largest leading submatrix whose estimated
36 1 pfleura2
*  condition number is less than 1/RCOND.  The order of R11, RANK,
37 1 pfleura2
*  is the effective rank of A.
38 1 pfleura2
*
39 1 pfleura2
*  Then, R22 is considered to be negligible, and R12 is annihilated
40 1 pfleura2
*  by orthogonal transformations from the right, arriving at the
41 1 pfleura2
*  complete orthogonal factorization:
42 1 pfleura2
*     A * P = Q * [ T11 0 ] * Z
43 1 pfleura2
*                 [  0  0 ]
44 1 pfleura2
*  The minimum-norm solution is then
45 1 pfleura2
*     X = P * Z' [ inv(T11)*Q1'*B ]
46 1 pfleura2
*                [        0       ]
47 1 pfleura2
*  where Q1 consists of the first RANK columns of Q.
48 1 pfleura2
*
49 1 pfleura2
*  This routine is basically identical to the original xGELSX except
50 1 pfleura2
*  three differences:
51 1 pfleura2
*    o The call to the subroutine xGEQPF has been substituted by the
52 1 pfleura2
*      the call to the subroutine xGEQP3. This subroutine is a Blas-3
53 1 pfleura2
*      version of the QR factorization with column pivoting.
54 1 pfleura2
*    o Matrix B (the right hand side) is updated with Blas-3.
55 1 pfleura2
*    o The permutation of matrix B (the right hand side) is faster and
56 1 pfleura2
*      more simple.
57 1 pfleura2
*
58 1 pfleura2
*  Arguments
59 1 pfleura2
*  =========
60 1 pfleura2
*
61 1 pfleura2
*  M       (input) INTEGER
62 1 pfleura2
*          The number of rows of the matrix A.  M >= 0.
63 1 pfleura2
*
64 1 pfleura2
*  N       (input) INTEGER
65 1 pfleura2
*          The number of columns of the matrix A.  N >= 0.
66 1 pfleura2
*
67 1 pfleura2
*  NRHS    (input) INTEGER
68 1 pfleura2
*          The number of right hand sides, i.e., the number of
69 1 pfleura2
*          columns of matrices B and X. NRHS >= 0.
70 1 pfleura2
*
71 1 pfleura2
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
72 1 pfleura2
*          On entry, the M-by-N matrix A.
73 1 pfleura2
*          On exit, A has been overwritten by details of its
74 1 pfleura2
*          complete orthogonal factorization.
75 1 pfleura2
*
76 1 pfleura2
*  LDA     (input) INTEGER
77 1 pfleura2
*          The leading dimension of the array A.  LDA >= max(1,M).
78 1 pfleura2
*
79 1 pfleura2
*  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
80 1 pfleura2
*          On entry, the M-by-NRHS right hand side matrix B.
81 1 pfleura2
*          On exit, the N-by-NRHS solution matrix X.
82 1 pfleura2
*
83 1 pfleura2
*  LDB     (input) INTEGER
84 1 pfleura2
*          The leading dimension of the array B. LDB >= max(1,M,N).
85 1 pfleura2
*
86 1 pfleura2
*  JPVT    (input/output) INTEGER array, dimension (N)
87 1 pfleura2
*          On entry, if JPVT(i) .ne. 0, the i-th column of A is permuted
88 1 pfleura2
*          to the front of AP, otherwise column i is a free column.
89 1 pfleura2
*          On exit, if JPVT(i) = k, then the i-th column of AP
90 1 pfleura2
*          was the k-th column of A.
91 1 pfleura2
*
92 1 pfleura2
*  RCOND   (input) DOUBLE PRECISION
93 1 pfleura2
*          RCOND is used to determine the effective rank of A, which
94 1 pfleura2
*          is defined as the order of the largest leading triangular
95 1 pfleura2
*          submatrix R11 in the QR factorization with pivoting of A,
96 1 pfleura2
*          whose estimated condition number < 1/RCOND.
97 1 pfleura2
*
98 1 pfleura2
*  RANK    (output) INTEGER
99 1 pfleura2
*          The effective rank of A, i.e., the order of the submatrix
100 1 pfleura2
*          R11.  This is the same as the order of the submatrix T11
101 1 pfleura2
*          in the complete orthogonal factorization of A.
102 1 pfleura2
*
103 1 pfleura2
*  WORK    (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
104 1 pfleura2
*          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
105 1 pfleura2
*
106 1 pfleura2
*  LWORK   (input) INTEGER
107 1 pfleura2
*          The dimension of the array WORK.
108 1 pfleura2
*          The unblocked strategy requires that:
109 1 pfleura2
*             LWORK >= MAX( MN+3*N+1, 2*MN+NRHS ),
110 1 pfleura2
*          where MN = min( M, N ).
111 1 pfleura2
*          The block algorithm requires that:
112 1 pfleura2
*             LWORK >= MAX( MN+2*N+NB*(N+1), 2*MN+NB*NRHS ),
113 1 pfleura2
*          where NB is an upper bound on the blocksize returned
114 1 pfleura2
*          by ILAENV for the routines DGEQP3, DTZRZF, STZRQF, DORMQR,
115 1 pfleura2
*          and DORMRZ.
116 1 pfleura2
*
117 1 pfleura2
*          If LWORK = -1, then a workspace query is assumed; the routine
118 1 pfleura2
*          only calculates the optimal size of the WORK array, returns
119 1 pfleura2
*          this value as the first entry of the WORK array, and no error
120 1 pfleura2
*          message related to LWORK is issued by XERBLA.
121 1 pfleura2
*
122 1 pfleura2
*  INFO    (output) INTEGER
123 1 pfleura2
*          = 0: successful exit
124 1 pfleura2
*          < 0: If INFO = -i, the i-th argument had an illegal value.
125 1 pfleura2
*
126 1 pfleura2
*  Further Details
127 1 pfleura2
*  ===============
128 1 pfleura2
*
129 1 pfleura2
*  Based on contributions by
130 1 pfleura2
*    A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA
131 1 pfleura2
*    E. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
132 1 pfleura2
*    G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
133 1 pfleura2
*
134 1 pfleura2
*  =====================================================================
135 1 pfleura2
*
136 1 pfleura2
*     .. Parameters ..
137 1 pfleura2
      INTEGER            IMAX, IMIN
138 1 pfleura2
      PARAMETER          ( IMAX = 1, IMIN = 2 )
139 1 pfleura2
      DOUBLE PRECISION   ZERO, ONE
140 1 pfleura2
      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
141 1 pfleura2
*     ..
142 1 pfleura2
*     .. Local Scalars ..
143 1 pfleura2
      LOGICAL            LQUERY
144 1 pfleura2
      INTEGER            I, IASCL, IBSCL, ISMAX, ISMIN, J, LWKMIN,
145 1 pfleura2
     $                   LWKOPT, MN, NB, NB1, NB2, NB3, NB4
146 1 pfleura2
      DOUBLE PRECISION   ANRM, BIGNUM, BNRM, C1, C2, S1, S2, SMAX,
147 1 pfleura2
     $                   SMAXPR, SMIN, SMINPR, SMLNUM, WSIZE
148 1 pfleura2
*     ..
149 1 pfleura2
*     .. External Functions ..
150 1 pfleura2
      INTEGER            ILAENV
151 1 pfleura2
      DOUBLE PRECISION   DLAMCH, DLANGE
152 1 pfleura2
      EXTERNAL           ILAENV, DLAMCH, DLANGE
153 1 pfleura2
*     ..
154 1 pfleura2
*     .. External Subroutines ..
155 1 pfleura2
      EXTERNAL           DCOPY, DGEQP3, DLABAD, DLAIC1, DLASCL, DLASET,
156 1 pfleura2
     $                   DORMQR, DORMRZ, DTRSM, DTZRZF, XERBLA
157 1 pfleura2
*     ..
158 1 pfleura2
*     .. Intrinsic Functions ..
159 1 pfleura2
      INTRINSIC          ABS, MAX, MIN
160 1 pfleura2
*     ..
161 1 pfleura2
*     .. Executable Statements ..
162 1 pfleura2
*
163 1 pfleura2
      MN = MIN( M, N )
164 1 pfleura2
      ISMIN = MN + 1
165 1 pfleura2
      ISMAX = 2*MN + 1
166 1 pfleura2
*
167 1 pfleura2
*     Test the input arguments.
168 1 pfleura2
*
169 1 pfleura2
      INFO = 0
170 1 pfleura2
      LQUERY = ( LWORK.EQ.-1 )
171 1 pfleura2
      IF( M.LT.0 ) THEN
172 1 pfleura2
         INFO = -1
173 1 pfleura2
      ELSE IF( N.LT.0 ) THEN
174 1 pfleura2
         INFO = -2
175 1 pfleura2
      ELSE IF( NRHS.LT.0 ) THEN
176 1 pfleura2
         INFO = -3
177 1 pfleura2
      ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
178 1 pfleura2
         INFO = -5
179 1 pfleura2
      ELSE IF( LDB.LT.MAX( 1, M, N ) ) THEN
180 1 pfleura2
         INFO = -7
181 1 pfleura2
      END IF
182 1 pfleura2
*
183 1 pfleura2
*     Figure out optimal block size
184 1 pfleura2
*
185 1 pfleura2
      IF( INFO.EQ.0 ) THEN
186 1 pfleura2
         IF( MN.EQ.0 .OR. NRHS.EQ.0 ) THEN
187 1 pfleura2
            LWKMIN = 1
188 1 pfleura2
            LWKOPT = 1
189 1 pfleura2
         ELSE
190 1 pfleura2
            NB1 = ILAENV( 1, 'DGEQRF', ' ', M, N, -1, -1 )
191 1 pfleura2
            NB2 = ILAENV( 1, 'DGERQF', ' ', M, N, -1, -1 )
192 1 pfleura2
            NB3 = ILAENV( 1, 'DORMQR', ' ', M, N, NRHS, -1 )
193 1 pfleura2
            NB4 = ILAENV( 1, 'DORMRQ', ' ', M, N, NRHS, -1 )
194 1 pfleura2
            NB = MAX( NB1, NB2, NB3, NB4 )
195 1 pfleura2
            LWKMIN = MN + MAX( 2*MN, N + 1, MN + NRHS )
196 1 pfleura2
            LWKOPT = MAX( LWKMIN,
197 1 pfleura2
     $                    MN + 2*N + NB*( N + 1 ), 2*MN + NB*NRHS )
198 1 pfleura2
         END IF
199 1 pfleura2
         WORK( 1 ) = LWKOPT
200 1 pfleura2
*
201 1 pfleura2
         IF( LWORK.LT.LWKMIN .AND. .NOT.LQUERY ) THEN
202 1 pfleura2
            INFO = -12
203 1 pfleura2
         END IF
204 1 pfleura2
      END IF
205 1 pfleura2
*
206 1 pfleura2
      IF( INFO.NE.0 ) THEN
207 1 pfleura2
         CALL XERBLA( 'DGELSY', -INFO )
208 1 pfleura2
         RETURN
209 1 pfleura2
      ELSE IF( LQUERY ) THEN
210 1 pfleura2
         RETURN
211 1 pfleura2
      END IF
212 1 pfleura2
*
213 1 pfleura2
*     Quick return if possible
214 1 pfleura2
*
215 1 pfleura2
      IF( MN.EQ.0 .OR. NRHS.EQ.0 ) THEN
216 1 pfleura2
         RANK = 0
217 1 pfleura2
         RETURN
218 1 pfleura2
      END IF
219 1 pfleura2
*
220 1 pfleura2
*     Get machine parameters
221 1 pfleura2
*
222 1 pfleura2
      SMLNUM = DLAMCH( 'S' ) / DLAMCH( 'P' )
223 1 pfleura2
      BIGNUM = ONE / SMLNUM
224 1 pfleura2
      CALL DLABAD( SMLNUM, BIGNUM )
225 1 pfleura2
*
226 1 pfleura2
*     Scale A, B if max entries outside range [SMLNUM,BIGNUM]
227 1 pfleura2
*
228 1 pfleura2
      ANRM = DLANGE( 'M', M, N, A, LDA, WORK )
229 1 pfleura2
      IASCL = 0
230 1 pfleura2
      IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
231 1 pfleura2
*
232 1 pfleura2
*        Scale matrix norm up to SMLNUM
233 1 pfleura2
*
234 1 pfleura2
         CALL DLASCL( 'G', 0, 0, ANRM, SMLNUM, M, N, A, LDA, INFO )
235 1 pfleura2
         IASCL = 1
236 1 pfleura2
      ELSE IF( ANRM.GT.BIGNUM ) THEN
237 1 pfleura2
*
238 1 pfleura2
*        Scale matrix norm down to BIGNUM
239 1 pfleura2
*
240 1 pfleura2
         CALL DLASCL( 'G', 0, 0, ANRM, BIGNUM, M, N, A, LDA, INFO )
241 1 pfleura2
         IASCL = 2
242 1 pfleura2
      ELSE IF( ANRM.EQ.ZERO ) THEN
243 1 pfleura2
*
244 1 pfleura2
*        Matrix all zero. Return zero solution.
245 1 pfleura2
*
246 1 pfleura2
         CALL DLASET( 'F', MAX( M, N ), NRHS, ZERO, ZERO, B, LDB )
247 1 pfleura2
         RANK = 0
248 1 pfleura2
         GO TO 70
249 1 pfleura2
      END IF
250 1 pfleura2
*
251 1 pfleura2
      BNRM = DLANGE( 'M', M, NRHS, B, LDB, WORK )
252 1 pfleura2
      IBSCL = 0
253 1 pfleura2
      IF( BNRM.GT.ZERO .AND. BNRM.LT.SMLNUM ) THEN
254 1 pfleura2
*
255 1 pfleura2
*        Scale matrix norm up to SMLNUM
256 1 pfleura2
*
257 1 pfleura2
         CALL DLASCL( 'G', 0, 0, BNRM, SMLNUM, M, NRHS, B, LDB, INFO )
258 1 pfleura2
         IBSCL = 1
259 1 pfleura2
      ELSE IF( BNRM.GT.BIGNUM ) THEN
260 1 pfleura2
*
261 1 pfleura2
*        Scale matrix norm down to BIGNUM
262 1 pfleura2
*
263 1 pfleura2
         CALL DLASCL( 'G', 0, 0, BNRM, BIGNUM, M, NRHS, B, LDB, INFO )
264 1 pfleura2
         IBSCL = 2
265 1 pfleura2
      END IF
266 1 pfleura2
*
267 1 pfleura2
*     Compute QR factorization with column pivoting of A:
268 1 pfleura2
*        A * P = Q * R
269 1 pfleura2
*
270 1 pfleura2
      CALL DGEQP3( M, N, A, LDA, JPVT, WORK( 1 ), WORK( MN+1 ),
271 1 pfleura2
     $             LWORK-MN, INFO )
272 1 pfleura2
      WSIZE = MN + WORK( MN+1 )
273 1 pfleura2
*
274 1 pfleura2
*     workspace: MN+2*N+NB*(N+1).
275 1 pfleura2
*     Details of Householder rotations stored in WORK(1:MN).
276 1 pfleura2
*
277 1 pfleura2
*     Determine RANK using incremental condition estimation
278 1 pfleura2
*
279 1 pfleura2
      WORK( ISMIN ) = ONE
280 1 pfleura2
      WORK( ISMAX ) = ONE
281 1 pfleura2
      SMAX = ABS( A( 1, 1 ) )
282 1 pfleura2
      SMIN = SMAX
283 1 pfleura2
      IF( ABS( A( 1, 1 ) ).EQ.ZERO ) THEN
284 1 pfleura2
         RANK = 0
285 1 pfleura2
         CALL DLASET( 'F', MAX( M, N ), NRHS, ZERO, ZERO, B, LDB )
286 1 pfleura2
         GO TO 70
287 1 pfleura2
      ELSE
288 1 pfleura2
         RANK = 1
289 1 pfleura2
      END IF
290 1 pfleura2
*
291 1 pfleura2
   10 CONTINUE
292 1 pfleura2
      IF( RANK.LT.MN ) THEN
293 1 pfleura2
         I = RANK + 1
294 1 pfleura2
         CALL DLAIC1( IMIN, RANK, WORK( ISMIN ), SMIN, A( 1, I ),
295 1 pfleura2
     $                A( I, I ), SMINPR, S1, C1 )
296 1 pfleura2
         CALL DLAIC1( IMAX, RANK, WORK( ISMAX ), SMAX, A( 1, I ),
297 1 pfleura2
     $                A( I, I ), SMAXPR, S2, C2 )
298 1 pfleura2
*
299 1 pfleura2
         IF( SMAXPR*RCOND.LE.SMINPR ) THEN
300 1 pfleura2
            DO 20 I = 1, RANK
301 1 pfleura2
               WORK( ISMIN+I-1 ) = S1*WORK( ISMIN+I-1 )
302 1 pfleura2
               WORK( ISMAX+I-1 ) = S2*WORK( ISMAX+I-1 )
303 1 pfleura2
   20       CONTINUE
304 1 pfleura2
            WORK( ISMIN+RANK ) = C1
305 1 pfleura2
            WORK( ISMAX+RANK ) = C2
306 1 pfleura2
            SMIN = SMINPR
307 1 pfleura2
            SMAX = SMAXPR
308 1 pfleura2
            RANK = RANK + 1
309 1 pfleura2
            GO TO 10
310 1 pfleura2
         END IF
311 1 pfleura2
      END IF
312 1 pfleura2
*
313 1 pfleura2
*     workspace: 3*MN.
314 1 pfleura2
*
315 1 pfleura2
*     Logically partition R = [ R11 R12 ]
316 1 pfleura2
*                             [  0  R22 ]
317 1 pfleura2
*     where R11 = R(1:RANK,1:RANK)
318 1 pfleura2
*
319 1 pfleura2
*     [R11,R12] = [ T11, 0 ] * Y
320 1 pfleura2
*
321 1 pfleura2
      IF( RANK.LT.N )
322 1 pfleura2
     $   CALL DTZRZF( RANK, N, A, LDA, WORK( MN+1 ), WORK( 2*MN+1 ),
323 1 pfleura2
     $                LWORK-2*MN, INFO )
324 1 pfleura2
*
325 1 pfleura2
*     workspace: 2*MN.
326 1 pfleura2
*     Details of Householder rotations stored in WORK(MN+1:2*MN)
327 1 pfleura2
*
328 1 pfleura2
*     B(1:M,1:NRHS) := Q' * B(1:M,1:NRHS)
329 1 pfleura2
*
330 1 pfleura2
      CALL DORMQR( 'Left', 'Transpose', M, NRHS, MN, A, LDA, WORK( 1 ),
331 1 pfleura2
     $             B, LDB, WORK( 2*MN+1 ), LWORK-2*MN, INFO )
332 1 pfleura2
      WSIZE = MAX( WSIZE, 2*MN+WORK( 2*MN+1 ) )
333 1 pfleura2
*
334 1 pfleura2
*     workspace: 2*MN+NB*NRHS.
335 1 pfleura2
*
336 1 pfleura2
*     B(1:RANK,1:NRHS) := inv(T11) * B(1:RANK,1:NRHS)
337 1 pfleura2
*
338 1 pfleura2
      CALL DTRSM( 'Left', 'Upper', 'No transpose', 'Non-unit', RANK,
339 1 pfleura2
     $            NRHS, ONE, A, LDA, B, LDB )
340 1 pfleura2
*
341 1 pfleura2
      DO 40 J = 1, NRHS
342 1 pfleura2
         DO 30 I = RANK + 1, N
343 1 pfleura2
            B( I, J ) = ZERO
344 1 pfleura2
   30    CONTINUE
345 1 pfleura2
   40 CONTINUE
346 1 pfleura2
*
347 1 pfleura2
*     B(1:N,1:NRHS) := Y' * B(1:N,1:NRHS)
348 1 pfleura2
*
349 1 pfleura2
      IF( RANK.LT.N ) THEN
350 1 pfleura2
         CALL DORMRZ( 'Left', 'Transpose', N, NRHS, RANK, N-RANK, A,
351 1 pfleura2
     $                LDA, WORK( MN+1 ), B, LDB, WORK( 2*MN+1 ),
352 1 pfleura2
     $                LWORK-2*MN, INFO )
353 1 pfleura2
      END IF
354 1 pfleura2
*
355 1 pfleura2
*     workspace: 2*MN+NRHS.
356 1 pfleura2
*
357 1 pfleura2
*     B(1:N,1:NRHS) := P * B(1:N,1:NRHS)
358 1 pfleura2
*
359 1 pfleura2
      DO 60 J = 1, NRHS
360 1 pfleura2
         DO 50 I = 1, N
361 1 pfleura2
            WORK( JPVT( I ) ) = B( I, J )
362 1 pfleura2
   50    CONTINUE
363 1 pfleura2
         CALL DCOPY( N, WORK( 1 ), 1, B( 1, J ), 1 )
364 1 pfleura2
   60 CONTINUE
365 1 pfleura2
*
366 1 pfleura2
*     workspace: N.
367 1 pfleura2
*
368 1 pfleura2
*     Undo scaling
369 1 pfleura2
*
370 1 pfleura2
      IF( IASCL.EQ.1 ) THEN
371 1 pfleura2
         CALL DLASCL( 'G', 0, 0, ANRM, SMLNUM, N, NRHS, B, LDB, INFO )
372 1 pfleura2
         CALL DLASCL( 'U', 0, 0, SMLNUM, ANRM, RANK, RANK, A, LDA,
373 1 pfleura2
     $                INFO )
374 1 pfleura2
      ELSE IF( IASCL.EQ.2 ) THEN
375 1 pfleura2
         CALL DLASCL( 'G', 0, 0, ANRM, BIGNUM, N, NRHS, B, LDB, INFO )
376 1 pfleura2
         CALL DLASCL( 'U', 0, 0, BIGNUM, ANRM, RANK, RANK, A, LDA,
377 1 pfleura2
     $                INFO )
378 1 pfleura2
      END IF
379 1 pfleura2
      IF( IBSCL.EQ.1 ) THEN
380 1 pfleura2
         CALL DLASCL( 'G', 0, 0, SMLNUM, BNRM, N, NRHS, B, LDB, INFO )
381 1 pfleura2
      ELSE IF( IBSCL.EQ.2 ) THEN
382 1 pfleura2
         CALL DLASCL( 'G', 0, 0, BIGNUM, BNRM, N, NRHS, B, LDB, INFO )
383 1 pfleura2
      END IF
384 1 pfleura2
*
385 1 pfleura2
   70 CONTINUE
386 1 pfleura2
      WORK( 1 ) = LWKOPT
387 1 pfleura2
*
388 1 pfleura2
      RETURN
389 1 pfleura2
*
390 1 pfleura2
*     End of DGELSY
391 1 pfleura2
*
392 1 pfleura2
      END