3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZGELQF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgelqf.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgelqf.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgelqf.f">
21 * SUBROUTINE ZGELQF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, LWORK, M, N
26 * .. Array Arguments ..
27 * COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * )
36 *> ZGELQF computes an LQ factorization of a complex M-by-N matrix A:
46 *> The number of rows of the matrix A. M >= 0.
52 *> The number of columns of the matrix A. N >= 0.
57 *> A is COMPLEX*16 array, dimension (LDA,N)
58 *> On entry, the M-by-N matrix A.
59 *> On exit, the elements on and below the diagonal of the array
60 *> contain the m-by-min(m,n) lower trapezoidal matrix L (L is
61 *> lower triangular if m <= n); the elements above the diagonal,
62 *> with the array TAU, represent the unitary matrix Q as a
63 *> product of elementary reflectors (see Further Details).
69 *> The leading dimension of the array A. LDA >= max(1,M).
74 *> TAU is COMPLEX*16 array, dimension (min(M,N))
75 *> The scalar factors of the elementary reflectors (see Further
81 *> WORK is COMPLEX*16 array, dimension (MAX(1,LWORK))
82 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
88 *> The dimension of the array WORK. LWORK >= max(1,M).
89 *> For optimum performance LWORK >= M*NB, where NB is the
92 *> If LWORK = -1, then a workspace query is assumed; the routine
93 *> only calculates the optimal size of the WORK array, returns
94 *> this value as the first entry of the WORK array, and no error
95 *> message related to LWORK is issued by XERBLA.
101 *> = 0: successful exit
102 *> < 0: if INFO = -i, the i-th argument had an illegal value
108 *> \author Univ. of Tennessee
109 *> \author Univ. of California Berkeley
110 *> \author Univ. of Colorado Denver
113 *> \date November 2011
115 *> \ingroup complex16GEcomputational
117 *> \par Further Details:
118 * =====================
122 *> The matrix Q is represented as a product of elementary reflectors
124 *> Q = H(k)**H . . . H(2)**H H(1)**H, where k = min(m,n).
126 *> Each H(i) has the form
128 *> H(i) = I - tau * v * v**H
130 *> where tau is a complex scalar, and v is a complex vector with
131 *> v(1:i-1) = 0 and v(i) = 1; conjg(v(i+1:n)) is stored on exit in
132 *> A(i,i+1:n), and tau in TAU(i).
135 * =====================================================================
136 SUBROUTINE ZGELQF( M, N, A, LDA, TAU, WORK, LWORK, INFO )
138 * -- LAPACK computational routine (version 3.4.0) --
139 * -- LAPACK is a software package provided by Univ. of Tennessee, --
140 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
143 * .. Scalar Arguments ..
144 INTEGER INFO, LDA, LWORK, M, N
146 * .. Array Arguments ..
147 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * )
150 * =====================================================================
152 * .. Local Scalars ..
154 INTEGER I, IB, IINFO, IWS, K, LDWORK, LWKOPT, NB,
157 * .. External Subroutines ..
158 EXTERNAL XERBLA, ZGELQ2, ZLARFB, ZLARFT
160 * .. Intrinsic Functions ..
163 * .. External Functions ..
167 * .. Executable Statements ..
169 * Test the input arguments
172 NB = ILAENV( 1, 'ZGELQF', ' ', M, N, -1, -1 )
175 LQUERY = ( LWORK.EQ.-1 )
178 ELSE IF( N.LT.0 ) THEN
180 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
182 ELSE IF( LWORK.LT.MAX( 1, M ) .AND. .NOT.LQUERY ) THEN
186 CALL XERBLA( 'ZGELQF', -INFO )
188 ELSE IF( LQUERY ) THEN
192 * Quick return if possible
203 IF( NB.GT.1 .AND. NB.LT.K ) THEN
205 * Determine when to cross over from blocked to unblocked code.
207 NX = MAX( 0, ILAENV( 3, 'ZGELQF', ' ', M, N, -1, -1 ) )
210 * Determine if workspace is large enough for blocked code.
214 IF( LWORK.LT.IWS ) THEN
216 * Not enough workspace to use optimal NB: reduce NB and
217 * determine the minimum value of NB.
220 NBMIN = MAX( 2, ILAENV( 2, 'ZGELQF', ' ', M, N, -1,
226 IF( NB.GE.NBMIN .AND. NB.LT.K .AND. NX.LT.K ) THEN
228 * Use blocked code initially
230 DO 10 I = 1, K - NX, NB
231 IB = MIN( K-I+1, NB )
233 * Compute the LQ factorization of the current block
236 CALL ZGELQ2( IB, N-I+1, A( I, I ), LDA, TAU( I ), WORK,
240 * Form the triangular factor of the block reflector
241 * H = H(i) H(i+1) . . . H(i+ib-1)
243 CALL ZLARFT( 'Forward', 'Rowwise', N-I+1, IB, A( I, I ),
244 $ LDA, TAU( I ), WORK, LDWORK )
246 * Apply H to A(i+ib:m,i:n) from the right
248 CALL ZLARFB( 'Right', 'No transpose', 'Forward',
249 $ 'Rowwise', M-I-IB+1, N-I+1, IB, A( I, I ),
250 $ LDA, WORK, LDWORK, A( I+IB, I ), LDA,
251 $ WORK( IB+1 ), LDWORK )
258 * Use unblocked code to factor the last or only block.
261 $ CALL ZGELQ2( M-I+1, N-I+1, A( I, I ), LDA, TAU( I ), WORK,