LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
zgelqf.f
Go to the documentation of this file.
1 *> \brief \b ZGELQF
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZGELQF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgelqf.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgelqf.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelqf.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZGELQF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, LWORK, M, N
25 * ..
26 * .. Array Arguments ..
27 * COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * )
28 * ..
29 *
30 *
31 *> \par Purpose:
32 * =============
33 *>
34 *> \verbatim
35 *>
36 *> ZGELQF computes an LQ factorization of a complex M-by-N matrix A:
37 *>
38 *> A = ( L 0 ) * Q
39 *>
40 *> where:
41 *>
42 *> Q is a N-by-N orthogonal matrix;
43 *> L is an lower-triangular M-by-M matrix;
44 *> 0 is a M-by-(N-M) zero matrix, if M < N.
45 *>
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] M
52 *> \verbatim
53 *> M is INTEGER
54 *> The number of rows of the matrix A. M >= 0.
55 *> \endverbatim
56 *>
57 *> \param[in] N
58 *> \verbatim
59 *> N is INTEGER
60 *> The number of columns of the matrix A. N >= 0.
61 *> \endverbatim
62 *>
63 *> \param[in,out] A
64 *> \verbatim
65 *> A is COMPLEX*16 array, dimension (LDA,N)
66 *> On entry, the M-by-N matrix A.
67 *> On exit, the elements on and below the diagonal of the array
68 *> contain the m-by-min(m,n) lower trapezoidal matrix L (L is
69 *> lower triangular if m <= n); the elements above the diagonal,
70 *> with the array TAU, represent the unitary matrix Q as a
71 *> product of elementary reflectors (see Further Details).
72 *> \endverbatim
73 *>
74 *> \param[in] LDA
75 *> \verbatim
76 *> LDA is INTEGER
77 *> The leading dimension of the array A. LDA >= max(1,M).
78 *> \endverbatim
79 *>
80 *> \param[out] TAU
81 *> \verbatim
82 *> TAU is COMPLEX*16 array, dimension (min(M,N))
83 *> The scalar factors of the elementary reflectors (see Further
84 *> Details).
85 *> \endverbatim
86 *>
87 *> \param[out] WORK
88 *> \verbatim
89 *> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
90 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
91 *> \endverbatim
92 *>
93 *> \param[in] LWORK
94 *> \verbatim
95 *> LWORK is INTEGER
96 *> The dimension of the array WORK. LWORK >= max(1,M).
97 *> For optimum performance LWORK >= M*NB, where NB is the
98 *> optimal blocksize.
99 *>
100 *> If LWORK = -1, then a workspace query is assumed; the routine
101 *> only calculates the optimal size of the WORK array, returns
102 *> this value as the first entry of the WORK array, and no error
103 *> message related to LWORK is issued by XERBLA.
104 *> \endverbatim
105 *>
106 *> \param[out] INFO
107 *> \verbatim
108 *> INFO is INTEGER
109 *> = 0: successful exit
110 *> < 0: if INFO = -i, the i-th argument had an illegal value
111 *> \endverbatim
112 *
113 * Authors:
114 * ========
115 *
116 *> \author Univ. of Tennessee
117 *> \author Univ. of California Berkeley
118 *> \author Univ. of Colorado Denver
119 *> \author NAG Ltd.
120 *
121 *> \date November 2019
122 *
123 *> \ingroup complex16GEcomputational
124 *
125 *> \par Further Details:
126 * =====================
127 *>
128 *> \verbatim
129 *>
130 *> The matrix Q is represented as a product of elementary reflectors
131 *>
132 *> Q = H(k)**H . . . H(2)**H H(1)**H, where k = min(m,n).
133 *>
134 *> Each H(i) has the form
135 *>
136 *> H(i) = I - tau * v * v**H
137 *>
138 *> where tau is a complex scalar, and v is a complex vector with
139 *> v(1:i-1) = 0 and v(i) = 1; conjg(v(i+1:n)) is stored on exit in
140 *> A(i,i+1:n), and tau in TAU(i).
141 *> \endverbatim
142 *>
143 * =====================================================================
144  SUBROUTINE zgelqf( M, N, A, LDA, TAU, WORK, LWORK, INFO )
145 *
146 * -- LAPACK computational routine (version 3.9.0) --
147 * -- LAPACK is a software package provided by Univ. of Tennessee, --
148 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149 * November 2019
150 *
151 * .. Scalar Arguments ..
152  INTEGER INFO, LDA, LWORK, M, N
153 * ..
154 * .. Array Arguments ..
155  COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * )
156 * ..
157 *
158 * =====================================================================
159 *
160 * .. Local Scalars ..
161  LOGICAL LQUERY
162  INTEGER I, IB, IINFO, IWS, K, LDWORK, LWKOPT, NB,
163  $ NBMIN, NX
164 * ..
165 * .. External Subroutines ..
166  EXTERNAL xerbla, zgelq2, zlarfb, zlarft
167 * ..
168 * .. Intrinsic Functions ..
169  INTRINSIC max, min
170 * ..
171 * .. External Functions ..
172  INTEGER ILAENV
173  EXTERNAL ilaenv
174 * ..
175 * .. Executable Statements ..
176 *
177 * Test the input arguments
178 *
179  info = 0
180  nb = ilaenv( 1, 'ZGELQF', ' ', m, n, -1, -1 )
181  lwkopt = m*nb
182  work( 1 ) = lwkopt
183  lquery = ( lwork.EQ.-1 )
184  IF( m.LT.0 ) THEN
185  info = -1
186  ELSE IF( n.LT.0 ) THEN
187  info = -2
188  ELSE IF( lda.LT.max( 1, m ) ) THEN
189  info = -4
190  ELSE IF( lwork.LT.max( 1, m ) .AND. .NOT.lquery ) THEN
191  info = -7
192  END IF
193  IF( info.NE.0 ) THEN
194  CALL xerbla( 'ZGELQF', -info )
195  RETURN
196  ELSE IF( lquery ) THEN
197  RETURN
198  END IF
199 *
200 * Quick return if possible
201 *
202  k = min( m, n )
203  IF( k.EQ.0 ) THEN
204  work( 1 ) = 1
205  RETURN
206  END IF
207 *
208  nbmin = 2
209  nx = 0
210  iws = m
211  IF( nb.GT.1 .AND. nb.LT.k ) THEN
212 *
213 * Determine when to cross over from blocked to unblocked code.
214 *
215  nx = max( 0, ilaenv( 3, 'ZGELQF', ' ', m, n, -1, -1 ) )
216  IF( nx.LT.k ) THEN
217 *
218 * Determine if workspace is large enough for blocked code.
219 *
220  ldwork = m
221  iws = ldwork*nb
222  IF( lwork.LT.iws ) THEN
223 *
224 * Not enough workspace to use optimal NB: reduce NB and
225 * determine the minimum value of NB.
226 *
227  nb = lwork / ldwork
228  nbmin = max( 2, ilaenv( 2, 'ZGELQF', ' ', m, n, -1,
229  $ -1 ) )
230  END IF
231  END IF
232  END IF
233 *
234  IF( nb.GE.nbmin .AND. nb.LT.k .AND. nx.LT.k ) THEN
235 *
236 * Use blocked code initially
237 *
238  DO 10 i = 1, k - nx, nb
239  ib = min( k-i+1, nb )
240 *
241 * Compute the LQ factorization of the current block
242 * A(i:i+ib-1,i:n)
243 *
244  CALL zgelq2( ib, n-i+1, a( i, i ), lda, tau( i ), work,
245  $ iinfo )
246  IF( i+ib.LE.m ) THEN
247 *
248 * Form the triangular factor of the block reflector
249 * H = H(i) H(i+1) . . . H(i+ib-1)
250 *
251  CALL zlarft( 'Forward', 'Rowwise', n-i+1, ib, a( i, i ),
252  $ lda, tau( i ), work, ldwork )
253 *
254 * Apply H to A(i+ib:m,i:n) from the right
255 *
256  CALL zlarfb( 'Right', 'No transpose', 'Forward',
257  $ 'Rowwise', m-i-ib+1, n-i+1, ib, a( i, i ),
258  $ lda, work, ldwork, a( i+ib, i ), lda,
259  $ work( ib+1 ), ldwork )
260  END IF
261  10 CONTINUE
262  ELSE
263  i = 1
264  END IF
265 *
266 * Use unblocked code to factor the last or only block.
267 *
268  IF( i.LE.k )
269  $ CALL zgelq2( m-i+1, n-i+1, a( i, i ), lda, tau( i ), work,
270  $ iinfo )
271 *
272  work( 1 ) = iws
273  RETURN
274 *
275 * End of ZGELQF
276 *
277  END
zlarfb
subroutine zlarfb(SIDE, TRANS, DIRECT, STOREV, M, N, K, V, LDV, T, LDT, C, LDC, WORK, LDWORK)
ZLARFB applies a block reflector or its conjugate-transpose to a general rectangular matrix.
Definition: zlarfb.f:199
zlarft
subroutine zlarft(DIRECT, STOREV, N, K, V, LDV, TAU, T, LDT)
ZLARFT forms the triangular factor T of a block reflector H = I - vtvH
Definition: zlarft.f:165
zgelqf
subroutine zgelqf(M, N, A, LDA, TAU, WORK, LWORK, INFO)
ZGELQF
Definition: zgelqf.f:145
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
zgelq2
subroutine zgelq2(M, N, A, LDA, TAU, WORK, INFO)
ZGELQ2 computes the LQ factorization of a general rectangular matrix using an unblocked algorithm.
Definition: zgelq2.f:131