LAPACK 3.12.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 172 of file cgelq.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 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 REAL SROUNDUP_LWORK
196 EXTERNAL lsame, sroundup_lwork
197* ..
198* .. External Subroutines ..
199 EXTERNAL cgelqt, claswlq, xerbla
200* ..
201* .. Intrinsic Functions ..
202 INTRINSIC max, min, mod
203* ..
204* .. External Functions ..
205 INTEGER ILAENV
206 EXTERNAL ilaenv
207* ..
208* .. Executable Statements ..
209*
210* Test the input arguments
211*
212 info = 0
213*
214 lquery = ( tsize.EQ.-1 .OR. tsize.EQ.-2 .OR.
215 $ lwork.EQ.-1 .OR. lwork.EQ.-2 )
216*
217 mint = .false.
218 minw = .false.
219 IF( tsize.EQ.-2 .OR. lwork.EQ.-2 ) THEN
220 IF( tsize.NE.-1 ) mint = .true.
221 IF( lwork.NE.-1 ) minw = .true.
222 END IF
223*
224* Determine the block size
225*
226 IF( min( m, n ).GT.0 ) THEN
227 mb = ilaenv( 1, 'CGELQ ', ' ', m, n, 1, -1 )
228 nb = ilaenv( 1, 'CGELQ ', ' ', m, n, 2, -1 )
229 ELSE
230 mb = 1
231 nb = n
232 END IF
233 IF( mb.GT.min( m, n ) .OR. mb.LT.1 ) mb = 1
234 IF( nb.GT.n .OR. nb.LE.m ) nb = n
235 mintsz = m + 5
236 IF( nb.GT.m .AND. n.GT.m ) THEN
237 IF( mod( n - m, nb - m ).EQ.0 ) THEN
238 nblcks = ( n - m ) / ( nb - m )
239 ELSE
240 nblcks = ( n - m ) / ( nb - m ) + 1
241 END IF
242 ELSE
243 nblcks = 1
244 END IF
245*
246* Determine if the workspace size satisfies minimal size
247*
248 IF( ( n.LE.m ) .OR. ( nb.LE.m ) .OR. ( nb.GE.n ) ) THEN
249 lwmin = max( 1, n )
250 lwopt = max( 1, mb*n )
251 ELSE
252 lwmin = max( 1, m )
253 lwopt = max( 1, mb*m )
254 END IF
255 lminws = .false.
256 IF( ( tsize.LT.max( 1, mb*m*nblcks + 5 ) .OR. lwork.LT.lwopt )
257 $ .AND. ( lwork.GE.lwmin ) .AND. ( tsize.GE.mintsz )
258 $ .AND. ( .NOT.lquery ) ) THEN
259 IF( tsize.LT.max( 1, mb*m*nblcks + 5 ) ) THEN
260 lminws = .true.
261 mb = 1
262 nb = n
263 END IF
264 IF( lwork.LT.lwopt ) THEN
265 lminws = .true.
266 mb = 1
267 END IF
268 END IF
269 IF( ( n.LE.m ) .OR. ( nb.LE.m ) .OR. ( nb.GE.n ) ) THEN
270 lwreq = max( 1, mb*n )
271 ELSE
272 lwreq = max( 1, mb*m )
273 END IF
274*
275 IF( m.LT.0 ) THEN
276 info = -1
277 ELSE IF( n.LT.0 ) THEN
278 info = -2
279 ELSE IF( lda.LT.max( 1, m ) ) THEN
280 info = -4
281 ELSE IF( tsize.LT.max( 1, mb*m*nblcks + 5 )
282 $ .AND. ( .NOT.lquery ) .AND. ( .NOT.lminws ) ) THEN
283 info = -6
284 ELSE IF( ( lwork.LT.lwreq ) .and .( .NOT.lquery )
285 $ .AND. ( .NOT.lminws ) ) THEN
286 info = -8
287 END IF
288*
289 IF( info.EQ.0 ) THEN
290 IF( mint ) THEN
291 t( 1 ) = mintsz
292 ELSE
293 t( 1 ) = mb*m*nblcks + 5
294 END IF
295 t( 2 ) = mb
296 t( 3 ) = nb
297 IF( minw ) THEN
298 work( 1 ) = sroundup_lwork(lwmin)
299 ELSE
300 work( 1 ) = sroundup_lwork(lwreq)
301 END IF
302 END IF
303 IF( info.NE.0 ) THEN
304 CALL xerbla( 'CGELQ', -info )
305 RETURN
306 ELSE IF( lquery ) THEN
307 RETURN
308 END IF
309*
310* Quick return if possible
311*
312 IF( min( m, n ).EQ.0 ) THEN
313 RETURN
314 END IF
315*
316* The LQ Decomposition
317*
318 IF( ( n.LE.m ) .OR. ( nb.LE.m ) .OR. ( nb.GE.n ) ) THEN
319 CALL cgelqt( m, n, mb, a, lda, t( 6 ), mb, work, info )
320 ELSE
321 CALL claswlq( m, n, mb, nb, a, lda, t( 6 ), mb, work,
322 $ lwork, info )
323 END IF
324*
325 work( 1 ) = sroundup_lwork(lwreq)
326*
327 RETURN
328*
329* End of CGELQ
330*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgelqt(m, n, mb, a, lda, t, ldt, work, info)
CGELQT
Definition cgelqt.f:124
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
subroutine claswlq(m, n, mb, nb, a, lda, t, ldt, work, lwork, info)
CLASWLQ
Definition claswlq.f:167
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
Here is the call graph for this function:
Here is the caller graph for this function: