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

◆ dgeqr()

subroutine dgeqr ( integer  m,
integer  n,
double precision, dimension( lda, * )  a,
integer  lda,
double precision, dimension( * )  t,
integer  tsize,
double precision, dimension( * )  work,
integer  lwork,
integer  info 
)

DGEQR

Purpose:
 DGEQR computes a QR factorization of a real M-by-N matrix A:

    A = Q * ( R ),
            ( 0 )

 where:

    Q is a M-by-M orthogonal matrix;
    R is an upper-triangular N-by-N matrix;
    0 is a (M-N)-by-N 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 DOUBLE PRECISION array, dimension (LDA,N)
          On entry, the M-by-N matrix A.
          On exit, the elements on and above the diagonal of the array
          contain the min(M,N)-by-N upper trapezoidal matrix R
          (R is upper triangular if M >= N);
          the elements below 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 DOUBLE PRECISION 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) DOUBLE PRECISION 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 QR factorization algorithm they wish. The triangular 
 (trapezoidal) R has to be stored in the upper 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
                           DLATSQR or DGEQRT

  Depending on the matrix dimensions M and N, and row and column
  block sizes MB and NB returned by ILAENV, DGEQR will use either
  DLATSQR (if the matrix is tall-and-skinny) or DGEQRT to compute
  the QR factorization.

Definition at line 174 of file dgeqr.f.

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