LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cgeqp3.f
Go to the documentation of this file.
1 *> \brief \b CGEQP3
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CGEQP3 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgeqp3.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgeqp3.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgeqp3.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CGEQP3( M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, LWORK, M, N
26 * ..
27 * .. Array Arguments ..
28 * INTEGER JPVT( * )
29 * REAL RWORK( * )
30 * COMPLEX A( LDA, * ), TAU( * ), WORK( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> CGEQP3 computes a QR factorization with column pivoting of a
40 *> matrix A: A*P = Q*R using Level 3 BLAS.
41 *> \endverbatim
42 *
43 * Arguments:
44 * ==========
45 *
46 *> \param[in] M
47 *> \verbatim
48 *> M is INTEGER
49 *> The number of rows of the matrix A. M >= 0.
50 *> \endverbatim
51 *>
52 *> \param[in] N
53 *> \verbatim
54 *> N is INTEGER
55 *> The number of columns of the matrix A. N >= 0.
56 *> \endverbatim
57 *>
58 *> \param[in,out] A
59 *> \verbatim
60 *> A is COMPLEX array, dimension (LDA,N)
61 *> On entry, the M-by-N matrix A.
62 *> On exit, the upper triangle of the array contains the
63 *> min(M,N)-by-N upper trapezoidal matrix R; the elements below
64 *> the diagonal, together with the array TAU, represent the
65 *> unitary matrix Q as a product of min(M,N) elementary
66 *> reflectors.
67 *> \endverbatim
68 *>
69 *> \param[in] LDA
70 *> \verbatim
71 *> LDA is INTEGER
72 *> The leading dimension of the array A. LDA >= max(1,M).
73 *> \endverbatim
74 *>
75 *> \param[in,out] JPVT
76 *> \verbatim
77 *> JPVT is INTEGER array, dimension (N)
78 *> On entry, if JPVT(J).ne.0, the J-th column of A is permuted
79 *> to the front of A*P (a leading column); if JPVT(J)=0,
80 *> the J-th column of A is a free column.
81 *> On exit, if JPVT(J)=K, then the J-th column of A*P was the
82 *> the K-th column of A.
83 *> \endverbatim
84 *>
85 *> \param[out] TAU
86 *> \verbatim
87 *> TAU is COMPLEX array, dimension (min(M,N))
88 *> The scalar factors of the elementary reflectors.
89 *> \endverbatim
90 *>
91 *> \param[out] WORK
92 *> \verbatim
93 *> WORK is COMPLEX array, dimension (MAX(1,LWORK))
94 *> On exit, if INFO=0, WORK(1) returns the optimal LWORK.
95 *> \endverbatim
96 *>
97 *> \param[in] LWORK
98 *> \verbatim
99 *> LWORK is INTEGER
100 *> The dimension of the array WORK. LWORK >= N+1.
101 *> For optimal performance LWORK >= ( N+1 )*NB, where NB
102 *> is the optimal blocksize.
103 *>
104 *> If LWORK = -1, then a workspace query is assumed; the routine
105 *> only calculates the optimal size of the WORK array, returns
106 *> this value as the first entry of the WORK array, and no error
107 *> message related to LWORK is issued by XERBLA.
108 *> \endverbatim
109 *>
110 *> \param[out] RWORK
111 *> \verbatim
112 *> RWORK is REAL array, dimension (2*N)
113 *> \endverbatim
114 *>
115 *> \param[out] INFO
116 *> \verbatim
117 *> INFO is INTEGER
118 *> = 0: successful exit.
119 *> < 0: if INFO = -i, the i-th argument had an illegal value.
120 *> \endverbatim
121 *
122 * Authors:
123 * ========
124 *
125 *> \author Univ. of Tennessee
126 *> \author Univ. of California Berkeley
127 *> \author Univ. of Colorado Denver
128 *> \author NAG Ltd.
129 *
130 *> \date November 2015
131 *
132 *> \ingroup complexGEcomputational
133 *
134 *> \par Further Details:
135 * =====================
136 *>
137 *> \verbatim
138 *>
139 *> The matrix Q is represented as a product of elementary reflectors
140 *>
141 *> Q = H(1) H(2) . . . H(k), where k = min(m,n).
142 *>
143 *> Each H(i) has the form
144 *>
145 *> H(i) = I - tau * v * v**H
146 *>
147 *> where tau is a complex scalar, and v is a real/complex vector
148 *> with v(1:i-1) = 0 and v(i) = 1; v(i+1:m) is stored on exit in
149 *> A(i+1:m,i), and tau in TAU(i).
150 *> \endverbatim
151 *
152 *> \par Contributors:
153 * ==================
154 *>
155 *> G. Quintana-Orti, Depto. de Informatica, Universidad Jaime I, Spain
156 *> X. Sun, Computer Science Dept., Duke University, USA
157 *>
158 * =====================================================================
159  SUBROUTINE cgeqp3( M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK,
160  $ info )
161 *
162 * -- LAPACK computational routine (version 3.6.0) --
163 * -- LAPACK is a software package provided by Univ. of Tennessee, --
164 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
165 * November 2015
166 *
167 * .. Scalar Arguments ..
168  INTEGER INFO, LDA, LWORK, M, N
169 * ..
170 * .. Array Arguments ..
171  INTEGER JPVT( * )
172  REAL RWORK( * )
173  COMPLEX A( lda, * ), TAU( * ), WORK( * )
174 * ..
175 *
176 * =====================================================================
177 *
178 * .. Parameters ..
179  INTEGER INB, INBMIN, IXOVER
180  parameter ( inb = 1, inbmin = 2, ixover = 3 )
181 * ..
182 * .. Local Scalars ..
183  LOGICAL LQUERY
184  INTEGER FJB, IWS, J, JB, LWKOPT, MINMN, MINWS, NA, NB,
185  $ nbmin, nfxd, nx, sm, sminmn, sn, topbmn
186 * ..
187 * .. External Subroutines ..
188  EXTERNAL cgeqrf, claqp2, claqps, cswap, cunmqr, xerbla
189 * ..
190 * .. External Functions ..
191  INTEGER ILAENV
192  REAL SCNRM2
193  EXTERNAL ilaenv, scnrm2
194 * ..
195 * .. Intrinsic Functions ..
196  INTRINSIC int, max, min
197 * ..
198 * .. Executable Statements ..
199 *
200 * Test input arguments
201 * ====================
202 *
203  info = 0
204  lquery = ( lwork.EQ.-1 )
205  IF( m.LT.0 ) THEN
206  info = -1
207  ELSE IF( n.LT.0 ) THEN
208  info = -2
209  ELSE IF( lda.LT.max( 1, m ) ) THEN
210  info = -4
211  END IF
212 *
213  IF( info.EQ.0 ) THEN
214  minmn = min( m, n )
215  IF( minmn.EQ.0 ) THEN
216  iws = 1
217  lwkopt = 1
218  ELSE
219  iws = n + 1
220  nb = ilaenv( inb, 'CGEQRF', ' ', m, n, -1, -1 )
221  lwkopt = ( n + 1 )*nb
222  END IF
223  work( 1 ) = cmplx( lwkopt )
224 *
225  IF( ( lwork.LT.iws ) .AND. .NOT.lquery ) THEN
226  info = -8
227  END IF
228  END IF
229 *
230  IF( info.NE.0 ) THEN
231  CALL xerbla( 'CGEQP3', -info )
232  RETURN
233  ELSE IF( lquery ) THEN
234  RETURN
235  END IF
236 *
237 * Move initial columns up front.
238 *
239  nfxd = 1
240  DO 10 j = 1, n
241  IF( jpvt( j ).NE.0 ) THEN
242  IF( j.NE.nfxd ) THEN
243  CALL cswap( m, a( 1, j ), 1, a( 1, nfxd ), 1 )
244  jpvt( j ) = jpvt( nfxd )
245  jpvt( nfxd ) = j
246  ELSE
247  jpvt( j ) = j
248  END IF
249  nfxd = nfxd + 1
250  ELSE
251  jpvt( j ) = j
252  END IF
253  10 CONTINUE
254  nfxd = nfxd - 1
255 *
256 * Factorize fixed columns
257 * =======================
258 *
259 * Compute the QR factorization of fixed columns and update
260 * remaining columns.
261 *
262  IF( nfxd.GT.0 ) THEN
263  na = min( m, nfxd )
264 *CC CALL CGEQR2( M, NA, A, LDA, TAU, WORK, INFO )
265  CALL cgeqrf( m, na, a, lda, tau, work, lwork, info )
266  iws = max( iws, int( work( 1 ) ) )
267  IF( na.LT.n ) THEN
268 *CC CALL CUNM2R( 'Left', 'Conjugate Transpose', M, N-NA,
269 *CC $ NA, A, LDA, TAU, A( 1, NA+1 ), LDA, WORK,
270 *CC $ INFO )
271  CALL cunmqr( 'Left', 'Conjugate Transpose', m, n-na, na, a,
272  $ lda, tau, a( 1, na+1 ), lda, work, lwork,
273  $ info )
274  iws = max( iws, int( work( 1 ) ) )
275  END IF
276  END IF
277 *
278 * Factorize free columns
279 * ======================
280 *
281  IF( nfxd.LT.minmn ) THEN
282 *
283  sm = m - nfxd
284  sn = n - nfxd
285  sminmn = minmn - nfxd
286 *
287 * Determine the block size.
288 *
289  nb = ilaenv( inb, 'CGEQRF', ' ', sm, sn, -1, -1 )
290  nbmin = 2
291  nx = 0
292 *
293  IF( ( nb.GT.1 ) .AND. ( nb.LT.sminmn ) ) THEN
294 *
295 * Determine when to cross over from blocked to unblocked code.
296 *
297  nx = max( 0, ilaenv( ixover, 'CGEQRF', ' ', sm, sn, -1,
298  $ -1 ) )
299 *
300 *
301  IF( nx.LT.sminmn ) THEN
302 *
303 * Determine if workspace is large enough for blocked code.
304 *
305  minws = ( sn+1 )*nb
306  iws = max( iws, minws )
307  IF( lwork.LT.minws ) THEN
308 *
309 * Not enough workspace to use optimal NB: Reduce NB and
310 * determine the minimum value of NB.
311 *
312  nb = lwork / ( sn+1 )
313  nbmin = max( 2, ilaenv( inbmin, 'CGEQRF', ' ', sm, sn,
314  $ -1, -1 ) )
315 *
316 *
317  END IF
318  END IF
319  END IF
320 *
321 * Initialize partial column norms. The first N elements of work
322 * store the exact column norms.
323 *
324  DO 20 j = nfxd + 1, n
325  rwork( j ) = scnrm2( sm, a( nfxd+1, j ), 1 )
326  rwork( n+j ) = rwork( j )
327  20 CONTINUE
328 *
329  IF( ( nb.GE.nbmin ) .AND. ( nb.LT.sminmn ) .AND.
330  $ ( nx.LT.sminmn ) ) THEN
331 *
332 * Use blocked code initially.
333 *
334  j = nfxd + 1
335 *
336 * Compute factorization: while loop.
337 *
338 *
339  topbmn = minmn - nx
340  30 CONTINUE
341  IF( j.LE.topbmn ) THEN
342  jb = min( nb, topbmn-j+1 )
343 *
344 * Factorize JB columns among columns J:N.
345 *
346  CALL claqps( m, n-j+1, j-1, jb, fjb, a( 1, j ), lda,
347  $ jpvt( j ), tau( j ), rwork( j ),
348  $ rwork( n+j ), work( 1 ), work( jb+1 ),
349  $ n-j+1 )
350 *
351  j = j + fjb
352  GO TO 30
353  END IF
354  ELSE
355  j = nfxd + 1
356  END IF
357 *
358 * Use unblocked code to factor the last or only block.
359 *
360 *
361  IF( j.LE.minmn )
362  $ CALL claqp2( m, n-j+1, j-1, a( 1, j ), lda, jpvt( j ),
363  $ tau( j ), rwork( j ), rwork( n+j ), work( 1 ) )
364 *
365  END IF
366 *
367  work( 1 ) = cmplx( lwkopt )
368  RETURN
369 *
370 * End of CGEQP3
371 *
372  END
subroutine claqp2(M, N, OFFSET, A, LDA, JPVT, TAU, VN1, VN2, WORK)
CLAQP2 computes a QR factorization with column pivoting of the matrix block.
Definition: claqp2.f:151
subroutine claqps(M, N, OFFSET, NB, KB, A, LDA, JPVT, TAU, VN1, VN2, AUXV, F, LDF)
CLAQPS computes a step of QR factorization with column pivoting of a real m-by-n matrix A by using BL...
Definition: claqps.f:180
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cunmqr(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
CUNMQR
Definition: cunmqr.f:170
subroutine cgeqp3(M, N, A, LDA, JPVT, TAU, WORK, LWORK, RWORK, INFO)
CGEQP3
Definition: cgeqp3.f:161
subroutine cgeqrf(M, N, A, LDA, TAU, WORK, LWORK, INFO)
CGEQRF
Definition: cgeqrf.f:138
subroutine cswap(N, CX, INCX, CY, INCY)
CSWAP
Definition: cswap.f:52