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