~ubuntu-branches/ubuntu/karmic/scilab/karmic

« back to all changes in this revision

Viewing changes to routines/lapack/dgelsx.f

  • Committer: Bazaar Package Importer
  • Author(s): Torsten Werner
  • Date: 2002-03-21 16:57:43 UTC
  • Revision ID: james.westby@ubuntu.com-20020321165743-e9mv12c1tb1plztg
Tags: upstream-2.6
ImportĀ upstreamĀ versionĀ 2.6

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
      SUBROUTINE DGELSX( M, N, NRHS, A, LDA, B, LDB, JPVT, RCOND, RANK,
 
2
     $                   WORK, INFO )
 
3
*
 
4
*  -- LAPACK driver routine (version 2.0) --
 
5
*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
 
6
*     Courant Institute, Argonne National Lab, and Rice University
 
7
*     March 31, 1993
 
8
*
 
9
*     .. Scalar Arguments ..
 
10
      INTEGER            INFO, LDA, LDB, M, N, NRHS, RANK
 
11
      DOUBLE PRECISION   RCOND
 
12
*     ..
 
13
*     .. Array Arguments ..
 
14
      INTEGER            JPVT( * )
 
15
      DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), WORK( * )
 
16
*     ..
 
17
*
 
18
*  Purpose
 
19
*  =======
 
20
*
 
21
*  DGELSX computes the minimum-norm solution to a real linear least
 
22
*  squares problem:
 
23
*      minimize || A * X - B ||
 
24
*  using a complete orthogonal factorization 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 routine first computes a QR factorization with column pivoting:
 
33
*      A * P = Q * [ R11 R12 ]
 
34
*                  [  0  R22 ]
 
35
*  with R11 defined as the largest leading submatrix whose estimated
 
36
*  condition number is less than 1/RCOND.  The order of R11, RANK,
 
37
*  is the effective rank of A.
 
38
*
 
39
*  Then, R22 is considered to be negligible, and R12 is annihilated
 
40
*  by orthogonal transformations from the right, arriving at the
 
41
*  complete orthogonal factorization:
 
42
*     A * P = Q * [ T11 0 ] * Z
 
43
*                 [  0  0 ]
 
44
*  The minimum-norm solution is then
 
45
*     X = P * Z' [ inv(T11)*Q1'*B ]
 
46
*                [        0       ]
 
47
*  where Q1 consists of the first RANK columns of Q.
 
48
*
 
49
*  Arguments
 
50
*  =========
 
51
*
 
52
*  M       (input) INTEGER
 
53
*          The number of rows of the matrix A.  M >= 0.
 
54
*
 
55
*  N       (input) INTEGER
 
56
*          The number of columns of the matrix A.  N >= 0.
 
57
*
 
58
*  NRHS    (input) INTEGER
 
59
*          The number of right hand sides, i.e., the number of
 
60
*          columns of matrices B and X. NRHS >= 0.
 
61
*
 
62
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
 
63
*          On entry, the M-by-N matrix A.
 
64
*          On exit, A has been overwritten by details of its
 
65
*          complete orthogonal factorization.
 
66
*
 
67
*  LDA     (input) INTEGER
 
68
*          The leading dimension of the array A.  LDA >= max(1,M).
 
69
*
 
70
*  B       (input/output) DOUBLE PRECISION array, dimension (LDB,NRHS)
 
71
*          On entry, the M-by-NRHS right hand side matrix B.
 
72
*          On exit, the N-by-NRHS solution matrix X.
 
73
*          If m >= n and RANK = n, the residual sum-of-squares for
 
74
*          the solution in the i-th column is given by the sum of
 
75
*          squares of elements N+1:M in that column.
 
76
*
 
77
*  LDB     (input) INTEGER
 
78
*          The leading dimension of the array B. LDB >= max(1,M,N).
 
79
*
 
80
*  JPVT    (input/output) INTEGER array, dimension (N)
 
81
*          On entry, if JPVT(i) .ne. 0, the i-th column of A is an
 
82
*          initial column, otherwise it is a free column.  Before
 
83
*          the QR factorization of A, all initial columns are
 
84
*          permuted to the leading positions; only the remaining
 
85
*          free columns are moved as a result of column pivoting
 
86
*          during the factorization.
 
87
*          On exit, if JPVT(i) = k, then the i-th column of A*P
 
88
*          was the k-th column of A.
 
89
*
 
90
*  RCOND   (input) DOUBLE PRECISION
 
91
*          RCOND is used to determine the effective rank of A, which
 
92
*          is defined as the order of the largest leading triangular
 
93
*          submatrix R11 in the QR factorization with pivoting of A,
 
94
*          whose estimated condition number < 1/RCOND.
 
95
*
 
96
*  RANK    (output) INTEGER
 
97
*          The effective rank of A, i.e., the order of the submatrix
 
98
*          R11.  This is the same as the order of the submatrix T11
 
99
*          in the complete orthogonal factorization of A.
 
100
*
 
101
*  WORK    (workspace) DOUBLE PRECISION array, dimension
 
102
*                      (max( min(M,N)+3*N, 2*min(M,N)+NRHS )),
 
103
*
 
104
*  INFO    (output) INTEGER
 
105
*          = 0:  successful exit
 
106
*          < 0:  if INFO = -i, the i-th argument had an illegal value
 
107
*
 
108
*  =====================================================================
 
109
*
 
110
*     .. Parameters ..
 
111
      INTEGER            IMAX, IMIN
 
112
      PARAMETER          ( IMAX = 1, IMIN = 2 )
 
113
      DOUBLE PRECISION   ZERO, ONE, DONE, NTDONE
 
114
      PARAMETER          ( ZERO = 0.0D0, ONE = 1.0D0, DONE = ZERO,
 
115
     $                   NTDONE = ONE )
 
116
*     ..
 
117
*     .. Local Scalars ..
 
118
      INTEGER            I, IASCL, IBSCL, ISMAX, ISMIN, J, K, MN
 
119
      DOUBLE PRECISION   ANRM, BIGNUM, BNRM, C1, C2, S1, S2, SMAX,
 
120
     $                   SMAXPR, SMIN, SMINPR, SMLNUM, T1, T2
 
121
*     ..
 
122
*     .. External Functions ..
 
123
      DOUBLE PRECISION   DLAMCH, DLANGE
 
124
      EXTERNAL           DLAMCH, DLANGE
 
125
*     ..
 
126
*     .. External Subroutines ..
 
127
      EXTERNAL           DGEQPF, DLABAD, DLAIC1, DLASCL, DLASET, DLATZM,
 
128
     $                   DORM2R, DTRSM, DTZRQF, XERBLA
 
129
*     ..
 
130
*     .. Intrinsic Functions ..
 
131
      INTRINSIC          ABS, MAX, MIN
 
132
*     ..
 
133
*     .. Executable Statements ..
 
134
*
 
135
      MN = MIN( M, N )
 
136
      ISMIN = MN + 1
 
137
      ISMAX = 2*MN + 1
 
138
*
 
139
*     Test the input arguments.
 
140
*
 
141
      INFO = 0
 
142
      IF( M.LT.0 ) THEN
 
143
         INFO = -1
 
144
      ELSE IF( N.LT.0 ) THEN
 
145
         INFO = -2
 
146
      ELSE IF( NRHS.LT.0 ) THEN
 
147
         INFO = -3
 
148
      ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
 
149
         INFO = -5
 
150
      ELSE IF( LDB.LT.MAX( 1, M, N ) ) THEN
 
151
         INFO = -7
 
152
      END IF
 
153
*
 
154
      IF( INFO.NE.0 ) THEN
 
155
         CALL XERBLA( 'DGELSX', -INFO )
 
156
         RETURN
 
157
      END IF
 
158
*
 
159
*     Quick return if possible
 
160
*
 
161
      IF( MIN( M, N, NRHS ).EQ.0 ) THEN
 
162
         RANK = 0
 
163
         RETURN
 
164
      END IF
 
165
*
 
166
*     Get machine parameters
 
167
*
 
168
      SMLNUM = DLAMCH( 'S' ) / DLAMCH( 'P' )
 
169
      BIGNUM = ONE / SMLNUM
 
170
      CALL DLABAD( SMLNUM, BIGNUM )
 
171
*
 
172
*     Scale A, B if max elements outside range [SMLNUM,BIGNUM]
 
173
*
 
174
      ANRM = DLANGE( 'M', M, N, A, LDA, WORK )
 
175
      IASCL = 0
 
176
      IF( ANRM.GT.ZERO .AND. ANRM.LT.SMLNUM ) THEN
 
177
*
 
178
*        Scale matrix norm up to SMLNUM
 
179
*
 
180
         CALL DLASCL( 'G', 0, 0, ANRM, SMLNUM, M, N, A, LDA, INFO )
 
181
         IASCL = 1
 
182
      ELSE IF( ANRM.GT.BIGNUM ) THEN
 
183
*
 
184
*        Scale matrix norm down to BIGNUM
 
185
*
 
186
         CALL DLASCL( 'G', 0, 0, ANRM, BIGNUM, M, N, A, LDA, INFO )
 
187
         IASCL = 2
 
188
      ELSE IF( ANRM.EQ.ZERO ) THEN
 
189
*
 
190
*        Matrix all zero. Return zero solution.
 
191
*
 
192
         CALL DLASET( 'F', MAX( M, N ), NRHS, ZERO, ZERO, B, LDB )
 
193
         RANK = 0
 
194
         GO TO 100
 
195
      END IF
 
196
*
 
197
      BNRM = DLANGE( 'M', M, NRHS, B, LDB, WORK )
 
198
      IBSCL = 0
 
199
      IF( BNRM.GT.ZERO .AND. BNRM.LT.SMLNUM ) THEN
 
200
*
 
201
*        Scale matrix norm up to SMLNUM
 
202
*
 
203
         CALL DLASCL( 'G', 0, 0, BNRM, SMLNUM, M, NRHS, B, LDB, INFO )
 
204
         IBSCL = 1
 
205
      ELSE IF( BNRM.GT.BIGNUM ) THEN
 
206
*
 
207
*        Scale matrix norm down to BIGNUM
 
208
*
 
209
         CALL DLASCL( 'G', 0, 0, BNRM, BIGNUM, M, NRHS, B, LDB, INFO )
 
210
         IBSCL = 2
 
211
      END IF
 
212
*
 
213
*     Compute QR factorization with column pivoting of A:
 
214
*        A * P = Q * R
 
215
*
 
216
      CALL DGEQPF( M, N, A, LDA, JPVT, WORK( 1 ), WORK( MN+1 ), INFO )
 
217
*
 
218
*     workspace 3*N. Details of Householder rotations stored
 
219
*     in WORK(1:MN).
 
220
*
 
221
*     Determine RANK using incremental condition estimation
 
222
*
 
223
      WORK( ISMIN ) = ONE
 
224
      WORK( ISMAX ) = ONE
 
225
      SMAX = ABS( A( 1, 1 ) )
 
226
      SMIN = SMAX
 
227
      IF( ABS( A( 1, 1 ) ).EQ.ZERO ) THEN
 
228
         RANK = 0
 
229
         CALL DLASET( 'F', MAX( M, N ), NRHS, ZERO, ZERO, B, LDB )
 
230
         GO TO 100
 
231
      ELSE
 
232
         RANK = 1
 
233
      END IF
 
234
*
 
235
   10 CONTINUE
 
236
      IF( RANK.LT.MN ) THEN
 
237
         I = RANK + 1
 
238
         CALL DLAIC1( IMIN, RANK, WORK( ISMIN ), SMIN, A( 1, I ),
 
239
     $                A( I, I ), SMINPR, S1, C1 )
 
240
         CALL DLAIC1( IMAX, RANK, WORK( ISMAX ), SMAX, A( 1, I ),
 
241
     $                A( I, I ), SMAXPR, S2, C2 )
 
242
*
 
243
         IF( SMAXPR*RCOND.LE.SMINPR ) THEN
 
244
            DO 20 I = 1, RANK
 
245
               WORK( ISMIN+I-1 ) = S1*WORK( ISMIN+I-1 )
 
246
               WORK( ISMAX+I-1 ) = S2*WORK( ISMAX+I-1 )
 
247
   20       CONTINUE
 
248
            WORK( ISMIN+RANK ) = C1
 
249
            WORK( ISMAX+RANK ) = C2
 
250
            SMIN = SMINPR
 
251
            SMAX = SMAXPR
 
252
            RANK = RANK + 1
 
253
            GO TO 10
 
254
         END IF
 
255
      END IF
 
256
*
 
257
*     Logically partition R = [ R11 R12 ]
 
258
*                             [  0  R22 ]
 
259
*     where R11 = R(1:RANK,1:RANK)
 
260
*
 
261
*     [R11,R12] = [ T11, 0 ] * Y
 
262
*
 
263
      IF( RANK.LT.N )
 
264
     $   CALL DTZRQF( RANK, N, A, LDA, WORK( MN+1 ), INFO )
 
265
*
 
266
*     Details of Householder rotations stored in WORK(MN+1:2*MN)
 
267
*
 
268
*     B(1:M,1:NRHS) := Q' * B(1:M,1:NRHS)
 
269
*
 
270
      CALL DORM2R( 'Left', 'Transpose', M, NRHS, MN, A, LDA, WORK( 1 ),
 
271
     $             B, LDB, WORK( 2*MN+1 ), INFO )
 
272
*
 
273
*     workspace NRHS
 
274
*
 
275
*     B(1:RANK,1:NRHS) := inv(T11) * B(1:RANK,1:NRHS)
 
276
*
 
277
      CALL DTRSM( 'Left', 'Upper', 'No transpose', 'Non-unit', RANK,
 
278
     $            NRHS, ONE, A, LDA, B, LDB )
 
279
*
 
280
      DO 40 I = RANK + 1, N
 
281
         DO 30 J = 1, NRHS
 
282
            B( I, J ) = ZERO
 
283
   30    CONTINUE
 
284
   40 CONTINUE
 
285
*
 
286
*     B(1:N,1:NRHS) := Y' * B(1:N,1:NRHS)
 
287
*
 
288
      IF( RANK.LT.N ) THEN
 
289
         DO 50 I = 1, RANK
 
290
            CALL DLATZM( 'Left', N-RANK+1, NRHS, A( I, RANK+1 ), LDA,
 
291
     $                   WORK( MN+I ), B( I, 1 ), B( RANK+1, 1 ), LDB,
 
292
     $                   WORK( 2*MN+1 ) )
 
293
   50    CONTINUE
 
294
      END IF
 
295
*
 
296
*     workspace NRHS
 
297
*
 
298
*     B(1:N,1:NRHS) := P * B(1:N,1:NRHS)
 
299
*
 
300
      DO 90 J = 1, NRHS
 
301
         DO 60 I = 1, N
 
302
            WORK( 2*MN+I ) = NTDONE
 
303
   60    CONTINUE
 
304
         DO 80 I = 1, N
 
305
            IF( WORK( 2*MN+I ).EQ.NTDONE ) THEN
 
306
               IF( JPVT( I ).NE.I ) THEN
 
307
                  K = I
 
308
                  T1 = B( K, J )
 
309
                  T2 = B( JPVT( K ), J )
 
310
   70             CONTINUE
 
311
                  B( JPVT( K ), J ) = T1
 
312
                  WORK( 2*MN+K ) = DONE
 
313
                  T1 = T2
 
314
                  K = JPVT( K )
 
315
                  T2 = B( JPVT( K ), J )
 
316
                  IF( JPVT( K ).NE.I )
 
317
     $               GO TO 70
 
318
                  B( I, J ) = T1
 
319
                  WORK( 2*MN+K ) = DONE
 
320
               END IF
 
321
            END IF
 
322
   80    CONTINUE
 
323
   90 CONTINUE
 
324
*
 
325
*     Undo scaling
 
326
*
 
327
      IF( IASCL.EQ.1 ) THEN
 
328
         CALL DLASCL( 'G', 0, 0, ANRM, SMLNUM, N, NRHS, B, LDB, INFO )
 
329
         CALL DLASCL( 'U', 0, 0, SMLNUM, ANRM, RANK, RANK, A, LDA,
 
330
     $                INFO )
 
331
      ELSE IF( IASCL.EQ.2 ) THEN
 
332
         CALL DLASCL( 'G', 0, 0, ANRM, BIGNUM, N, NRHS, B, LDB, INFO )
 
333
         CALL DLASCL( 'U', 0, 0, BIGNUM, ANRM, RANK, RANK, A, LDA,
 
334
     $                INFO )
 
335
      END IF
 
336
      IF( IBSCL.EQ.1 ) THEN
 
337
         CALL DLASCL( 'G', 0, 0, SMLNUM, BNRM, N, NRHS, B, LDB, INFO )
 
338
      ELSE IF( IBSCL.EQ.2 ) THEN
 
339
         CALL DLASCL( 'G', 0, 0, BIGNUM, BNRM, N, NRHS, B, LDB, INFO )
 
340
      END IF
 
341
*
 
342
  100 CONTINUE
 
343
*
 
344
      RETURN
 
345
*
 
346
*     End of DGELSX
 
347
*
 
348
      END