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

◆ 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 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 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 170 of file cgelq.f.

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