142 SUBROUTINE dgeqrt( M, N, NB, A, LDA, T, LDT, WORK, INFO )
150 INTEGER INFO, LDA, LDT, M, N, NB
153 DOUBLE PRECISION A( lda, * ), T( ldt, * ), WORK( * )
160 INTEGER I, IB, IINFO, K
161 LOGICAL USE_RECURSIVE_QR
162 parameter( use_recursive_qr=.true. )
174 ELSE IF( n.LT.0 )
THEN
176 ELSE IF( nb.LT.1 .OR. ( nb.GT.min(m,n) .AND. min(m,n).GT.0 ) )
THEN
178 ELSE IF( lda.LT.max( 1, m ) )
THEN
180 ELSE IF( ldt.LT.nb )
THEN
184 CALL xerbla(
'DGEQRT', -info )
196 ib = min( k-i+1, nb )
200 IF( use_recursive_qr )
THEN
201 CALL dgeqrt3( m-i+1, ib, a(i,i), lda, t(1,i), ldt, iinfo )
203 CALL dgeqrt2( m-i+1, ib, a(i,i), lda, t(1,i), ldt, iinfo )
209 CALL dlarfb(
'L',
'T',
'F',
'C', m-i+1, n-i-ib+1, ib,
210 $ a( i, i ), lda, t( 1, i ), ldt,
211 $ a( i, i+ib ), lda, work , n-i-ib+1 )
subroutine dlarfb(SIDE, TRANS, DIRECT, STOREV, M, N, K, V, LDV, T, LDT, C, LDC, WORK, LDWORK)
DLARFB applies a block reflector or its transpose to a general rectangular matrix.
recursive subroutine dgeqrt3(M, N, A, LDA, T, LDT, INFO)
DGEQRT3 recursively computes a QR factorization of a general real or complex matrix using the compact...
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine dgeqrt(M, N, NB, A, LDA, T, LDT, WORK, INFO)
DGEQRT
subroutine dgeqrt2(M, N, A, LDA, T, LDT, INFO)
DGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY represen...