Statistiques
| Révision :

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

Historique | Voir | Annoter | Télécharger (8,3 ko)

1 1 pfleura2
      SUBROUTINE DGEQP3( M, N, A, LDA, JPVT, TAU, WORK, LWORK, INFO )
2 1 pfleura2
*
3 1 pfleura2
*  -- LAPACK routine (version 3.2) --
4 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
5 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 1 pfleura2
*     November 2006
7 1 pfleura2
*
8 1 pfleura2
*     .. Scalar Arguments ..
9 1 pfleura2
      INTEGER            INFO, LDA, LWORK, M, N
10 1 pfleura2
*     ..
11 1 pfleura2
*     .. Array Arguments ..
12 1 pfleura2
      INTEGER            JPVT( * )
13 1 pfleura2
      DOUBLE PRECISION   A( LDA, * ), TAU( * ), WORK( * )
14 1 pfleura2
*     ..
15 1 pfleura2
*
16 1 pfleura2
*  Purpose
17 1 pfleura2
*  =======
18 1 pfleura2
*
19 1 pfleura2
*  DGEQP3 computes a QR factorization with column pivoting of a
20 1 pfleura2
*  matrix A:  A*P = Q*R  using Level 3 BLAS.
21 1 pfleura2
*
22 1 pfleura2
*  Arguments
23 1 pfleura2
*  =========
24 1 pfleura2
*
25 1 pfleura2
*  M       (input) INTEGER
26 1 pfleura2
*          The number of rows of the matrix A. M >= 0.
27 1 pfleura2
*
28 1 pfleura2
*  N       (input) INTEGER
29 1 pfleura2
*          The number of columns of the matrix A.  N >= 0.
30 1 pfleura2
*
31 1 pfleura2
*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
32 1 pfleura2
*          On entry, the M-by-N matrix A.
33 1 pfleura2
*          On exit, the upper triangle of the array contains the
34 1 pfleura2
*          min(M,N)-by-N upper trapezoidal matrix R; the elements below
35 1 pfleura2
*          the diagonal, together with the array TAU, represent the
36 1 pfleura2
*          orthogonal matrix Q as a product of min(M,N) elementary
37 1 pfleura2
*          reflectors.
38 1 pfleura2
*
39 1 pfleura2
*  LDA     (input) INTEGER
40 1 pfleura2
*          The leading dimension of the array A. LDA >= max(1,M).
41 1 pfleura2
*
42 1 pfleura2
*  JPVT    (input/output) INTEGER array, dimension (N)
43 1 pfleura2
*          On entry, if JPVT(J).ne.0, the J-th column of A is permuted
44 1 pfleura2
*          to the front of A*P (a leading column); if JPVT(J)=0,
45 1 pfleura2
*          the J-th column of A is a free column.
46 1 pfleura2
*          On exit, if JPVT(J)=K, then the J-th column of A*P was the
47 1 pfleura2
*          the K-th column of A.
48 1 pfleura2
*
49 1 pfleura2
*  TAU     (output) DOUBLE PRECISION array, dimension (min(M,N))
50 1 pfleura2
*          The scalar factors of the elementary reflectors.
51 1 pfleura2
*
52 1 pfleura2
*  WORK    (workspace/output) DOUBLE PRECISION array, dimension (MAX(1,LWORK))
53 1 pfleura2
*          On exit, if INFO=0, WORK(1) returns the optimal LWORK.
54 1 pfleura2
*
55 1 pfleura2
*  LWORK   (input) INTEGER
56 1 pfleura2
*          The dimension of the array WORK. LWORK >= 3*N+1.
57 1 pfleura2
*          For optimal performance LWORK >= 2*N+( N+1 )*NB, where NB
58 1 pfleura2
*          is the optimal blocksize.
59 1 pfleura2
*
60 1 pfleura2
*          If LWORK = -1, then a workspace query is assumed; the routine
61 1 pfleura2
*          only calculates the optimal size of the WORK array, returns
62 1 pfleura2
*          this value as the first entry of the WORK array, and no error
63 1 pfleura2
*          message related to LWORK is issued by XERBLA.
64 1 pfleura2
*
65 1 pfleura2
*  INFO    (output) INTEGER
66 1 pfleura2
*          = 0: successful exit.
67 1 pfleura2
*          < 0: if INFO = -i, the i-th argument had an illegal value.
68 1 pfleura2
*
69 1 pfleura2
*  Further Details
70 1 pfleura2
*  ===============
71 1 pfleura2
*
72 1 pfleura2
*  The matrix Q is represented as a product of elementary reflectors
73 1 pfleura2
*
74 1 pfleura2
*     Q = H(1) H(2) . . . H(k), where k = min(m,n).
75 1 pfleura2
*
76 1 pfleura2
*  Each H(i) has the form
77 1 pfleura2
*
78 1 pfleura2
*     H(i) = I - tau * v * v'
79 1 pfleura2
*
80 1 pfleura2
*  where tau is a real/complex scalar, and v is a real/complex vector
81 1 pfleura2
*  with v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in
82 1 pfleura2
*  A(i+1:m,i), and tau in TAU(i).
83 1 pfleura2
*
84 1 pfleura2
*  Based on contributions by
85 1 pfleura2
*    G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
86 1 pfleura2
*    X. Sun, Computer Science Dept., Duke University, USA
87 1 pfleura2
*
88 1 pfleura2
*  =====================================================================
89 1 pfleura2
*
90 1 pfleura2
*     .. Parameters ..
91 1 pfleura2
      INTEGER            INB, INBMIN, IXOVER
92 1 pfleura2
      PARAMETER          ( INB = 1, INBMIN = 2, IXOVER = 3 )
93 1 pfleura2
*     ..
94 1 pfleura2
*     .. Local Scalars ..
95 1 pfleura2
      LOGICAL            LQUERY
96 1 pfleura2
      INTEGER            FJB, IWS, J, JB, LWKOPT, MINMN, MINWS, NA, NB,
97 1 pfleura2
     $                   NBMIN, NFXD, NX, SM, SMINMN, SN, TOPBMN
98 1 pfleura2
*     ..
99 1 pfleura2
*     .. External Subroutines ..
100 1 pfleura2
      EXTERNAL           DGEQRF, DLAQP2, DLAQPS, DORMQR, DSWAP, XERBLA
101 1 pfleura2
*     ..
102 1 pfleura2
*     .. External Functions ..
103 1 pfleura2
      INTEGER            ILAENV
104 1 pfleura2
      DOUBLE PRECISION   DNRM2
105 1 pfleura2
      EXTERNAL           ILAENV, DNRM2
106 1 pfleura2
*     ..
107 1 pfleura2
*     .. Intrinsic Functions ..
108 1 pfleura2
      INTRINSIC          INT, MAX, MIN
109 1 pfleura2
*     ..
110 1 pfleura2
*     .. Executable Statements ..
111 1 pfleura2
*
112 1 pfleura2
*     Test input arguments
113 1 pfleura2
*     ====================
114 1 pfleura2
*
115 1 pfleura2
      INFO = 0
116 1 pfleura2
      LQUERY = ( LWORK.EQ.-1 )
117 1 pfleura2
      IF( M.LT.0 ) THEN
118 1 pfleura2
         INFO = -1
119 1 pfleura2
      ELSE IF( N.LT.0 ) THEN
120 1 pfleura2
         INFO = -2
121 1 pfleura2
      ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
122 1 pfleura2
         INFO = -4
123 1 pfleura2
      END IF
124 1 pfleura2
*
125 1 pfleura2
      IF( INFO.EQ.0 ) THEN
126 1 pfleura2
         MINMN = MIN( M, N )
127 1 pfleura2
         IF( MINMN.EQ.0 ) THEN
128 1 pfleura2
            IWS = 1
129 1 pfleura2
            LWKOPT = 1
130 1 pfleura2
         ELSE
131 1 pfleura2
            IWS = 3*N + 1
132 1 pfleura2
            NB = ILAENV( INB, 'DGEQRF', ' ', M, N, -1, -1 )
133 1 pfleura2
            LWKOPT = 2*N + ( N + 1 )*NB
134 1 pfleura2
         END IF
135 1 pfleura2
         WORK( 1 ) = LWKOPT
136 1 pfleura2
*
137 1 pfleura2
         IF( ( LWORK.LT.IWS ) .AND. .NOT.LQUERY ) THEN
138 1 pfleura2
            INFO = -8
139 1 pfleura2
         END IF
140 1 pfleura2
      END IF
141 1 pfleura2
*
142 1 pfleura2
      IF( INFO.NE.0 ) THEN
143 1 pfleura2
         CALL XERBLA( 'DGEQP3', -INFO )
144 1 pfleura2
         RETURN
145 1 pfleura2
      ELSE IF( LQUERY ) THEN
146 1 pfleura2
         RETURN
147 1 pfleura2
      END IF
148 1 pfleura2
*
149 1 pfleura2
*     Quick return if possible.
150 1 pfleura2
*
151 1 pfleura2
      IF( MINMN.EQ.0 ) THEN
152 1 pfleura2
         RETURN
153 1 pfleura2
      END IF
154 1 pfleura2
*
155 1 pfleura2
*     Move initial columns up front.
156 1 pfleura2
*
157 1 pfleura2
      NFXD = 1
158 1 pfleura2
      DO 10 J = 1, N
159 1 pfleura2
         IF( JPVT( J ).NE.0 ) THEN
160 1 pfleura2
            IF( J.NE.NFXD ) THEN
161 1 pfleura2
               CALL DSWAP( M, A( 1, J ), 1, A( 1, NFXD ), 1 )
162 1 pfleura2
               JPVT( J ) = JPVT( NFXD )
163 1 pfleura2
               JPVT( NFXD ) = J
164 1 pfleura2
            ELSE
165 1 pfleura2
               JPVT( J ) = J
166 1 pfleura2
            END IF
167 1 pfleura2
            NFXD = NFXD + 1
168 1 pfleura2
         ELSE
169 1 pfleura2
            JPVT( J ) = J
170 1 pfleura2
         END IF
171 1 pfleura2
   10 CONTINUE
172 1 pfleura2
      NFXD = NFXD - 1
173 1 pfleura2
*
174 1 pfleura2
*     Factorize fixed columns
175 1 pfleura2
*     =======================
176 1 pfleura2
*
177 1 pfleura2
*     Compute the QR factorization of fixed columns and update
178 1 pfleura2
*     remaining columns.
179 1 pfleura2
*
180 1 pfleura2
      IF( NFXD.GT.0 ) THEN
181 1 pfleura2
         NA = MIN( M, NFXD )
182 1 pfleura2
*CC      CALL DGEQR2( M, NA, A, LDA, TAU, WORK, INFO )
183 1 pfleura2
         CALL DGEQRF( M, NA, A, LDA, TAU, WORK, LWORK, INFO )
184 1 pfleura2
         IWS = MAX( IWS, INT( WORK( 1 ) ) )
185 1 pfleura2
         IF( NA.LT.N ) THEN
186 1 pfleura2
*CC         CALL DORM2R( 'Left', 'Transpose', M, N-NA, NA, A, LDA,
187 1 pfleura2
*CC  $                   TAU, A( 1, NA+1 ), LDA, WORK, INFO )
188 1 pfleura2
            CALL DORMQR( 'Left', 'Transpose', M, N-NA, NA, A, LDA, TAU,
189 1 pfleura2
     $                   A( 1, NA+1 ), LDA, WORK, LWORK, INFO )
190 1 pfleura2
            IWS = MAX( IWS, INT( WORK( 1 ) ) )
191 1 pfleura2
         END IF
192 1 pfleura2
      END IF
193 1 pfleura2
*
194 1 pfleura2
*     Factorize free columns
195 1 pfleura2
*     ======================
196 1 pfleura2
*
197 1 pfleura2
      IF( NFXD.LT.MINMN ) THEN
198 1 pfleura2
*
199 1 pfleura2
         SM = M - NFXD
200 1 pfleura2
         SN = N - NFXD
201 1 pfleura2
         SMINMN = MINMN - NFXD
202 1 pfleura2
*
203 1 pfleura2
*        Determine the block size.
204 1 pfleura2
*
205 1 pfleura2
         NB = ILAENV( INB, 'DGEQRF', ' ', SM, SN, -1, -1 )
206 1 pfleura2
         NBMIN = 2
207 1 pfleura2
         NX = 0
208 1 pfleura2
*
209 1 pfleura2
         IF( ( NB.GT.1 ) .AND. ( NB.LT.SMINMN ) ) THEN
210 1 pfleura2
*
211 1 pfleura2
*           Determine when to cross over from blocked to unblocked code.
212 1 pfleura2
*
213 1 pfleura2
            NX = MAX( 0, ILAENV( IXOVER, 'DGEQRF', ' ', SM, SN, -1,
214 1 pfleura2
     $           -1 ) )
215 1 pfleura2
*
216 1 pfleura2
*
217 1 pfleura2
            IF( NX.LT.SMINMN ) THEN
218 1 pfleura2
*
219 1 pfleura2
*              Determine if workspace is large enough for blocked code.
220 1 pfleura2
*
221 1 pfleura2
               MINWS = 2*SN + ( SN+1 )*NB
222 1 pfleura2
               IWS = MAX( IWS, MINWS )
223 1 pfleura2
               IF( LWORK.LT.MINWS ) THEN
224 1 pfleura2
*
225 1 pfleura2
*                 Not enough workspace to use optimal NB: Reduce NB and
226 1 pfleura2
*                 determine the minimum value of NB.
227 1 pfleura2
*
228 1 pfleura2
                  NB = ( LWORK-2*SN ) / ( SN+1 )
229 1 pfleura2
                  NBMIN = MAX( 2, ILAENV( INBMIN, 'DGEQRF', ' ', SM, SN,
230 1 pfleura2
     $                    -1, -1 ) )
231 1 pfleura2
*
232 1 pfleura2
*
233 1 pfleura2
               END IF
234 1 pfleura2
            END IF
235 1 pfleura2
         END IF
236 1 pfleura2
*
237 1 pfleura2
*        Initialize partial column norms. The first N elements of work
238 1 pfleura2
*        store the exact column norms.
239 1 pfleura2
*
240 1 pfleura2
         DO 20 J = NFXD + 1, N
241 1 pfleura2
            WORK( J ) = DNRM2( SM, A( NFXD+1, J ), 1 )
242 1 pfleura2
            WORK( N+J ) = WORK( J )
243 1 pfleura2
   20    CONTINUE
244 1 pfleura2
*
245 1 pfleura2
         IF( ( NB.GE.NBMIN ) .AND. ( NB.LT.SMINMN ) .AND.
246 1 pfleura2
     $       ( NX.LT.SMINMN ) ) THEN
247 1 pfleura2
*
248 1 pfleura2
*           Use blocked code initially.
249 1 pfleura2
*
250 1 pfleura2
            J = NFXD + 1
251 1 pfleura2
*
252 1 pfleura2
*           Compute factorization: while loop.
253 1 pfleura2
*
254 1 pfleura2
*
255 1 pfleura2
            TOPBMN = MINMN - NX
256 1 pfleura2
   30       CONTINUE
257 1 pfleura2
            IF( J.LE.TOPBMN ) THEN
258 1 pfleura2
               JB = MIN( NB, TOPBMN-J+1 )
259 1 pfleura2
*
260 1 pfleura2
*              Factorize JB columns among columns J:N.
261 1 pfleura2
*
262 1 pfleura2
               CALL DLAQPS( M, N-J+1, J-1, JB, FJB, A( 1, J ), LDA,
263 1 pfleura2
     $                      JPVT( J ), TAU( J ), WORK( J ), WORK( N+J ),
264 1 pfleura2
     $                      WORK( 2*N+1 ), WORK( 2*N+JB+1 ), N-J+1 )
265 1 pfleura2
*
266 1 pfleura2
               J = J + FJB
267 1 pfleura2
               GO TO 30
268 1 pfleura2
            END IF
269 1 pfleura2
         ELSE
270 1 pfleura2
            J = NFXD + 1
271 1 pfleura2
         END IF
272 1 pfleura2
*
273 1 pfleura2
*        Use unblocked code to factor the last or only block.
274 1 pfleura2
*
275 1 pfleura2
*
276 1 pfleura2
         IF( J.LE.MINMN )
277 1 pfleura2
     $      CALL DLAQP2( M, N-J+1, J-1, A( 1, J ), LDA, JPVT( J ),
278 1 pfleura2
     $                   TAU( J ), WORK( J ), WORK( N+J ),
279 1 pfleura2
     $                   WORK( 2*N+1 ) )
280 1 pfleura2
*
281 1 pfleura2
      END IF
282 1 pfleura2
*
283 1 pfleura2
      WORK( 1 ) = IWS
284 1 pfleura2
      RETURN
285 1 pfleura2
*
286 1 pfleura2
*     End of DGEQP3
287 1 pfleura2
*
288 1 pfleura2
      END