LAPACK  3.9.0
LAPACK: Linear Algebra PACKage

◆ cgelq()

subroutine cgelq ( integer  M,
integer  N,
complex, dimension( lda, * )  A,
integer  LDA,
complex, dimension( * )  T,
integer  TSIZE,
complex, dimension( * )  WORK,
integer  LWORK,
integer  INFO 
)

CGELQ

Purpose:
 CGELQ 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 an 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 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 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 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
                           CLASWLQ or CGELQT

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

Definition at line 172 of file cgelq.f.

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