LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
zgeqr.f
Go to the documentation of this file.
1*> \brief \b ZGEQR
2*
3* Definition:
4* ===========
5*
6* SUBROUTINE ZGEQR( M, N, A, LDA, T, TSIZE, WORK, LWORK,
7* INFO )
8*
9* .. Scalar Arguments ..
10* INTEGER INFO, LDA, M, N, TSIZE, LWORK
11* ..
12* .. Array Arguments ..
13* COMPLEX*16 A( LDA, * ), T( * ), WORK( * )
14* ..
15*
16*
17*> \par Purpose:
18* =============
19*>
20*> \verbatim
21*>
22*> ZGEQR computes a QR factorization of a complex M-by-N matrix A:
23*>
24*> A = Q * ( R ),
25*> ( 0 )
26*>
27*> where:
28*>
29*> Q is a M-by-M orthogonal matrix;
30*> R is an upper-triangular N-by-N matrix;
31*> 0 is a (M-N)-by-N zero matrix, if M > N.
32*>
33*> \endverbatim
34*
35* Arguments:
36* ==========
37*
38*> \param[in] M
39*> \verbatim
40*> M is INTEGER
41*> The number of rows of the matrix A. M >= 0.
42*> \endverbatim
43*>
44*> \param[in] N
45*> \verbatim
46*> N is INTEGER
47*> The number of columns of the matrix A. N >= 0.
48*> \endverbatim
49*>
50*> \param[in,out] A
51*> \verbatim
52*> A is COMPLEX*16 array, dimension (LDA,N)
53*> On entry, the M-by-N matrix A.
54*> On exit, the elements on and above the diagonal of the array
55*> contain the min(M,N)-by-N upper trapezoidal matrix R
56*> (R is upper triangular if M >= N);
57*> the elements below the diagonal are used to store part of the
58*> data structure to represent Q.
59*> \endverbatim
60*>
61*> \param[in] LDA
62*> \verbatim
63*> LDA is INTEGER
64*> The leading dimension of the array A. LDA >= max(1,M).
65*> \endverbatim
66*>
67*> \param[out] T
68*> \verbatim
69*> T is COMPLEX*16 array, dimension (MAX(5,TSIZE))
70*> On exit, if INFO = 0, T(1) returns optimal (or either minimal
71*> or optimal, if query is assumed) TSIZE. See TSIZE for details.
72*> Remaining T contains part of the data structure used to represent Q.
73*> If one wants to apply or construct Q, then one needs to keep T
74*> (in addition to A) and pass it to further subroutines.
75*> \endverbatim
76*>
77*> \param[in] TSIZE
78*> \verbatim
79*> TSIZE is INTEGER
80*> If TSIZE >= 5, the dimension of the array T.
81*> If TSIZE = -1 or -2, then a workspace query is assumed. The routine
82*> only calculates the sizes of the T and WORK arrays, returns these
83*> values as the first entries of the T and WORK arrays, and no error
84*> message related to T or WORK is issued by XERBLA.
85*> If TSIZE = -1, the routine calculates optimal size of T for the
86*> optimum performance and returns this value in T(1).
87*> If TSIZE = -2, the routine calculates minimal size of T and
88*> returns this value in T(1).
89*> \endverbatim
90*>
91*> \param[out] WORK
92*> \verbatim
93*> (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK))
94*> On exit, if INFO = 0, WORK(1) contains optimal (or either minimal
95*> or optimal, if query was assumed) LWORK.
96*> See LWORK for details.
97*> \endverbatim
98*>
99*> \param[in] LWORK
100*> \verbatim
101*> LWORK is INTEGER
102*> The dimension of the array WORK.
103*> If LWORK = -1 or -2, then a workspace query is assumed. The routine
104*> only calculates the sizes of the T and WORK arrays, returns these
105*> values as the first entries of the T and WORK arrays, and no error
106*> message related to T or WORK is issued by XERBLA.
107*> If LWORK = -1, the routine calculates optimal size of WORK for the
108*> optimal performance and returns this value in WORK(1).
109*> If LWORK = -2, the routine calculates minimal size of WORK and
110*> returns this value in WORK(1).
111*> \endverbatim
112*>
113*> \param[out] INFO
114*> \verbatim
115*> INFO is INTEGER
116*> = 0: successful exit
117*> < 0: if INFO = -i, the i-th argument had an illegal value
118*> \endverbatim
119*
120* Authors:
121* ========
122*
123*> \author Univ. of Tennessee
124*> \author Univ. of California Berkeley
125*> \author Univ. of Colorado Denver
126*> \author NAG Ltd.
127*
128*> \par Further Details
129* ====================
130*>
131*> \verbatim
132*>
133*> The goal of the interface is to give maximum freedom to the developers for
134*> creating any QR factorization algorithm they wish. The triangular
135*> (trapezoidal) R has to be stored in the upper part of A. The lower part of A
136*> and the array T can be used to store any relevant information for applying or
137*> constructing the Q factor. The WORK array can safely be discarded after exit.
138*>
139*> Caution: One should not expect the sizes of T and WORK to be the same from one
140*> LAPACK implementation to the other, or even from one execution to the other.
141*> A workspace query (for T and WORK) is needed at each execution. However,
142*> for a given execution, the size of T and WORK are fixed and will not change
143*> from one query to the next.
144*>
145*> \endverbatim
146*>
147*> \par Further Details particular to this LAPACK implementation:
148* ==============================================================
149*>
150*> \verbatim
151*>
152*> These details are particular for this LAPACK implementation. Users should not
153*> take them for granted. These details may change in the future, and are not likely
154*> true for another LAPACK implementation. These details are relevant if one wants
155*> to try to understand the code. They are not part of the interface.
156*>
157*> In this version,
158*>
159*> T(2): row block size (MB)
160*> T(3): column block size (NB)
161*> T(6:TSIZE): data structure needed for Q, computed by
162*> ZLATSQR or ZGEQRT
163*>
164*> Depending on the matrix dimensions M and N, and row and column
165*> block sizes MB and NB returned by ILAENV, ZGEQR will use either
166*> ZLATSQR (if the matrix is tall-and-skinny) or ZGEQRT to compute
167*> the QR factorization.
168*>
169*> \endverbatim
170*>
171*> \ingroup geqr
172*>
173* =====================================================================
174 SUBROUTINE zgeqr( M, N, A, LDA, T, TSIZE, WORK, LWORK,
175 $ INFO )
176*
177* -- LAPACK computational routine --
178* -- LAPACK is a software package provided by Univ. of Tennessee, --
179* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd. --
180*
181* .. Scalar Arguments ..
182 INTEGER INFO, LDA, M, N, TSIZE, LWORK
183* ..
184* .. Array Arguments ..
185 COMPLEX*16 A( LDA, * ), T( * ), WORK( * )
186* ..
187*
188* =====================================================================
189*
190* ..
191* .. Local Scalars ..
192 LOGICAL LQUERY, LMINWS, MINT, MINW
193 INTEGER MB, NB, MINTSZ, NBLCKS
194* ..
195* .. External Functions ..
196 LOGICAL LSAME
197 EXTERNAL lsame
198* ..
199* .. External Subroutines ..
200 EXTERNAL zlatsqr, zgeqrt, xerbla
201* ..
202* .. Intrinsic Functions ..
203 INTRINSIC max, min, mod
204* ..
205* .. External Functions ..
206 INTEGER ILAENV
207 EXTERNAL ilaenv
208* ..
209* .. Executable Statements ..
210*
211* Test the input arguments
212*
213 info = 0
214*
215 lquery = ( tsize.EQ.-1 .OR. tsize.EQ.-2 .OR.
216 $ lwork.EQ.-1 .OR. lwork.EQ.-2 )
217*
218 mint = .false.
219 minw = .false.
220 IF( tsize.EQ.-2 .OR. lwork.EQ.-2 ) THEN
221 IF( tsize.NE.-1 ) mint = .true.
222 IF( lwork.NE.-1 ) minw = .true.
223 END IF
224*
225* Determine the block size
226*
227 IF( min( m, n ).GT.0 ) THEN
228 mb = ilaenv( 1, 'ZGEQR ', ' ', m, n, 1, -1 )
229 nb = ilaenv( 1, 'ZGEQR ', ' ', m, n, 2, -1 )
230 ELSE
231 mb = m
232 nb = 1
233 END IF
234 IF( mb.GT.m .OR. mb.LE.n ) mb = m
235 IF( nb.GT.min( m, n ) .OR. nb.LT.1 ) nb = 1
236 mintsz = n + 5
237 IF( mb.GT.n .AND. m.GT.n ) THEN
238 IF( mod( m - n, mb - n ).EQ.0 ) THEN
239 nblcks = ( m - n ) / ( mb - n )
240 ELSE
241 nblcks = ( m - n ) / ( mb - n ) + 1
242 END IF
243 ELSE
244 nblcks = 1
245 END IF
246*
247* Determine if the workspace size satisfies minimal size
248*
249 lminws = .false.
250 IF( ( tsize.LT.max( 1, nb*n*nblcks + 5 ) .OR. lwork.LT.nb*n )
251 $ .AND. ( lwork.GE.n ) .AND. ( tsize.GE.mintsz )
252 $ .AND. ( .NOT.lquery ) ) THEN
253 IF( tsize.LT.max( 1, nb*n*nblcks + 5 ) ) THEN
254 lminws = .true.
255 nb = 1
256 mb = m
257 END IF
258 IF( lwork.LT.nb*n ) THEN
259 lminws = .true.
260 nb = 1
261 END IF
262 END IF
263*
264 IF( m.LT.0 ) THEN
265 info = -1
266 ELSE IF( n.LT.0 ) THEN
267 info = -2
268 ELSE IF( lda.LT.max( 1, m ) ) THEN
269 info = -4
270 ELSE IF( tsize.LT.max( 1, nb*n*nblcks + 5 )
271 $ .AND. ( .NOT.lquery ) .AND. ( .NOT.lminws ) ) THEN
272 info = -6
273 ELSE IF( ( lwork.LT.max( 1, n*nb ) ) .AND. ( .NOT.lquery )
274 $ .AND. ( .NOT.lminws ) ) THEN
275 info = -8
276 END IF
277*
278 IF( info.EQ.0 ) THEN
279 IF( mint ) THEN
280 t( 1 ) = mintsz
281 ELSE
282 t( 1 ) = nb*n*nblcks + 5
283 END IF
284 t( 2 ) = mb
285 t( 3 ) = nb
286 IF( minw ) THEN
287 work( 1 ) = max( 1, n )
288 ELSE
289 work( 1 ) = max( 1, nb*n )
290 END IF
291 END IF
292 IF( info.NE.0 ) THEN
293 CALL xerbla( 'ZGEQR', -info )
294 RETURN
295 ELSE IF( lquery ) THEN
296 RETURN
297 END IF
298*
299* Quick return if possible
300*
301 IF( min( m, n ).EQ.0 ) THEN
302 RETURN
303 END IF
304*
305* The QR Decomposition
306*
307 IF( ( m.LE.n ) .OR. ( mb.LE.n ) .OR. ( mb.GE.m ) ) THEN
308 CALL zgeqrt( m, n, nb, a, lda, t( 6 ), nb, work, info )
309 ELSE
310 CALL zlatsqr( m, n, mb, nb, a, lda, t( 6 ), nb, work,
311 $ lwork, info )
312 END IF
313*
314 work( 1 ) = max( 1, nb*n )
315*
316 RETURN
317*
318* End of ZGEQR
319*
320 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgeqr(m, n, a, lda, t, tsize, work, lwork, info)
ZGEQR
Definition zgeqr.f:176
subroutine zgeqrt(m, n, nb, a, lda, t, ldt, work, info)
ZGEQRT
Definition zgeqrt.f:141
subroutine zlatsqr(m, n, mb, nb, a, lda, t, ldt, work, lwork, info)
ZLATSQR
Definition zlatsqr.f:169