LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zgelq()

subroutine zgelq ( integer  m,
integer  n,
complex*16, dimension( lda, * )  a,
integer  lda,
complex*16, dimension( * )  t,
integer  tsize,
complex*16, dimension( * )  work,
integer  lwork,
integer  info 
)

ZGELQ

Purpose:
 ZGELQ computes an LQ factorization of a complex M-by-N matrix A:

    A = ( L 0 ) *  Q

 where:

    Q is a N-by-N orthogonal matrix;
    L is a lower-triangular M-by-M matrix;
    0 is a M-by-(N-M) zero matrix, if M < N.
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrix A.  M >= 0.
[in]N
          N is INTEGER
          The number of columns of the matrix A.  N >= 0.
[in,out]A
          A is COMPLEX*16 array, dimension (LDA,N)
          On entry, the M-by-N matrix A.
          On exit, the elements on and below the diagonal of the array
          contain the M-by-min(M,N) lower trapezoidal matrix L
          (L is lower triangular if M <= N);
          the elements above the diagonal are used to store part of the 
          data structure to represent Q.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,M).
[out]T
          T is COMPLEX*16 array, dimension (MAX(5,TSIZE))
          On exit, if INFO = 0, T(1) returns optimal (or either minimal 
          or optimal, if query is assumed) TSIZE. See TSIZE for details.
          Remaining T contains part of the data structure used to represent Q.
          If one wants to apply or construct Q, then one needs to keep T 
          (in addition to A) and pass it to further subroutines.
[in]TSIZE
          TSIZE is INTEGER
          If TSIZE >= 5, the dimension of the array T.
          If TSIZE = -1 or -2, then a workspace query is assumed. The routine
          only calculates the sizes of the T and WORK arrays, returns these
          values as the first entries of the T and WORK arrays, and no error
          message related to T or WORK is issued by XERBLA.
          If TSIZE = -1, the routine calculates optimal size of T for the 
          optimum performance and returns this value in T(1).
          If TSIZE = -2, the routine calculates minimal size of T and 
          returns this value in T(1).
[out]WORK
          (workspace) COMPLEX*16 array, dimension (MAX(1,LWORK))
          On exit, if INFO = 0, WORK(1) contains optimal (or either minimal
          or optimal, if query was assumed) LWORK.
          See LWORK for details.
[in]LWORK
          LWORK is INTEGER
          The dimension of the array WORK.
          If LWORK = -1 or -2, then a workspace query is assumed. The routine
          only calculates the sizes of the T and WORK arrays, returns these
          values as the first entries of the T and WORK arrays, and no error
          message related to T or WORK is issued by XERBLA.
          If LWORK = -1, the routine calculates optimal size of WORK for the
          optimal performance and returns this value in WORK(1).
          If LWORK = -2, the routine calculates minimal size of WORK and 
          returns this value in WORK(1).
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details
 The goal of the interface is to give maximum freedom to the developers for
 creating any LQ factorization algorithm they wish. The triangular 
 (trapezoidal) L has to be stored in the lower part of A. The lower part of A
 and the array T can be used to store any relevant information for applying or
 constructing the Q factor. The WORK array can safely be discarded after exit.

 Caution: One should not expect the sizes of T and WORK to be the same from one 
 LAPACK implementation to the other, or even from one execution to the other.
 A workspace query (for T and WORK) is needed at each execution. However, 
 for a given execution, the size of T and WORK are fixed and will not change 
 from one query to the next.
Further Details particular to this LAPACK implementation:
 These details are particular for this LAPACK implementation. Users should not 
 take them for granted. These details may change in the future, and are not likely
 true for another LAPACK implementation. These details are relevant if one wants
 to try to understand the code. They are not part of the interface.

 In this version,

          T(2): row block size (MB)
          T(3): column block size (NB)
          T(6:TSIZE): data structure needed for Q, computed by
                           ZLASWLQ or ZGELQT

  Depending on the matrix dimensions M and N, and row and column
  block sizes MB and NB returned by ILAENV, ZGELQ will use either
  ZLASWLQ (if the matrix is short-and-wide) or ZGELQT to compute
  the LQ factorization.

Definition at line 172 of file zgelq.f.

174*
175* -- LAPACK computational routine --
176* -- LAPACK is a software package provided by Univ. of Tennessee, --
177* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd. --
178*
179* .. Scalar Arguments ..
180 INTEGER INFO, LDA, M, N, TSIZE, LWORK
181* ..
182* .. Array Arguments ..
183 COMPLEX*16 A( LDA, * ), T( * ), WORK( * )
184* ..
185*
186* =====================================================================
187*
188* ..
189* .. Local Scalars ..
190 LOGICAL LQUERY, LMINWS, MINT, MINW
191 INTEGER MB, NB, MINTSZ, NBLCKS, LWMIN, LWOPT, LWREQ
192* ..
193* .. External Functions ..
194 LOGICAL LSAME
195 EXTERNAL lsame
196* ..
197* .. External Subroutines ..
198 EXTERNAL zgelqt, zlaswlq, xerbla
199* ..
200* .. Intrinsic Functions ..
201 INTRINSIC max, min, mod
202* ..
203* .. External Functions ..
204 INTEGER ILAENV
205 EXTERNAL ilaenv
206* ..
207* .. Executable Statements ..
208*
209* Test the input arguments
210*
211 info = 0
212*
213 lquery = ( tsize.EQ.-1 .OR. tsize.EQ.-2 .OR.
214 $ lwork.EQ.-1 .OR. lwork.EQ.-2 )
215*
216 mint = .false.
217 minw = .false.
218 IF( tsize.EQ.-2 .OR. lwork.EQ.-2 ) THEN
219 IF( tsize.NE.-1 ) mint = .true.
220 IF( lwork.NE.-1 ) minw = .true.
221 END IF
222*
223* Determine the block size
224*
225 IF( min( m, n ).GT.0 ) THEN
226 mb = ilaenv( 1, 'ZGELQ ', ' ', m, n, 1, -1 )
227 nb = ilaenv( 1, 'ZGELQ ', ' ', m, n, 2, -1 )
228 ELSE
229 mb = 1
230 nb = n
231 END IF
232 IF( mb.GT.min( m, n ) .OR. mb.LT.1 ) mb = 1
233 IF( nb.GT.n .OR. nb.LE.m ) nb = n
234 mintsz = m + 5
235 IF ( nb.GT.m .AND. n.GT.m ) THEN
236 IF( mod( n - m, nb - m ).EQ.0 ) THEN
237 nblcks = ( n - m ) / ( nb - m )
238 ELSE
239 nblcks = ( n - m ) / ( nb - m ) + 1
240 END IF
241 ELSE
242 nblcks = 1
243 END IF
244*
245* Determine if the workspace size satisfies minimal size
246*
247 IF( ( n.LE.m ) .OR. ( nb.LE.m ) .OR. ( nb.GE.n ) ) THEN
248 lwmin = max( 1, n )
249 lwopt = max( 1, mb*n )
250 ELSE
251 lwmin = max( 1, m )
252 lwopt = max( 1, mb*m )
253 END IF
254 lminws = .false.
255 IF( ( tsize.LT.max( 1, mb*m*nblcks + 5 ) .OR. lwork.LT.lwopt )
256 $ .AND. ( lwork.GE.lwmin ) .AND. ( tsize.GE.mintsz )
257 $ .AND. ( .NOT.lquery ) ) THEN
258 IF( tsize.LT.max( 1, mb*m*nblcks + 5 ) ) THEN
259 lminws = .true.
260 mb = 1
261 nb = n
262 END IF
263 IF( lwork.LT.lwopt ) THEN
264 lminws = .true.
265 mb = 1
266 END IF
267 END IF
268 IF( ( n.LE.m ) .OR. ( nb.LE.m ) .OR. ( nb.GE.n ) ) THEN
269 lwreq = max( 1, mb*n )
270 ELSE
271 lwreq = max( 1, mb*m )
272 END IF
273*
274 IF( m.LT.0 ) THEN
275 info = -1
276 ELSE IF( n.LT.0 ) THEN
277 info = -2
278 ELSE IF( lda.LT.max( 1, m ) ) THEN
279 info = -4
280 ELSE IF( tsize.LT.max( 1, mb*m*nblcks + 5 )
281 $ .AND. ( .NOT.lquery ) .AND. ( .NOT.lminws ) ) THEN
282 info = -6
283 ELSE IF( ( lwork.LT.lwreq ) .and .( .NOT.lquery )
284 $ .AND. ( .NOT.lminws ) ) THEN
285 info = -8
286 END IF
287*
288 IF( info.EQ.0 ) THEN
289 IF( mint ) THEN
290 t( 1 ) = mintsz
291 ELSE
292 t( 1 ) = mb*m*nblcks + 5
293 END IF
294 t( 2 ) = mb
295 t( 3 ) = nb
296 IF( minw ) THEN
297 work( 1 ) = lwmin
298 ELSE
299 work( 1 ) = lwreq
300 END IF
301 END IF
302 IF( info.NE.0 ) THEN
303 CALL xerbla( 'ZGELQ', -info )
304 RETURN
305 ELSE IF( lquery ) THEN
306 RETURN
307 END IF
308*
309* Quick return if possible
310*
311 IF( min( m, n ).EQ.0 ) THEN
312 RETURN
313 END IF
314*
315* The LQ Decomposition
316*
317 IF( ( n.LE.m ) .OR. ( nb.LE.m ) .OR. ( nb.GE.n ) ) THEN
318 CALL zgelqt( m, n, mb, a, lda, t( 6 ), mb, work, info )
319 ELSE
320 CALL zlaswlq( m, n, mb, nb, a, lda, t( 6 ), mb, work,
321 $ lwork, info )
322 END IF
323*
324 work( 1 ) = lwreq
325*
326 RETURN
327*
328* End of ZGELQ
329*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zgelqt(m, n, mb, a, lda, t, ldt, work, info)
ZGELQT
Definition zgelqt.f:139
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
subroutine zlaswlq(m, n, mb, nb, a, lda, t, ldt, work, lwork, info)
ZLASWLQ
Definition zlaswlq.f:167
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: