140 SUBROUTINE sgeqrt( M, N, NB, A, LDA, T, LDT, WORK, INFO )
147 INTEGER INFO, LDA, LDT, M, N, NB
150 REAL A( LDA, * ), T( LDT, * ), WORK( * )
157 INTEGER I, IB, IINFO, K
158 LOGICAL USE_RECURSIVE_QR
159 parameter( use_recursive_qr=.true. )
171 ELSE IF( n.LT.0 )
THEN
173 ELSE IF( nb.LT.1 .OR. ( nb.GT.min(m,n) .AND. min(m,n).GT.0 ) )
THEN
175 ELSE IF( lda.LT.max( 1, m ) )
THEN
177 ELSE IF( ldt.LT.nb )
THEN
181 CALL xerbla(
'SGEQRT', -info )
193 ib = min( k-i+1, nb )
197 IF( use_recursive_qr )
THEN
198 CALL sgeqrt3( m-i+1, ib, a(i,i), lda, t(1,i), ldt, iinfo )
200 CALL sgeqrt2( m-i+1, ib, a(i,i), lda, t(1,i), ldt, iinfo )
206 CALL slarfb(
'L',
'T',
'F',
'C', m-i+1, n-i-ib+1, ib,
207 $ a( i, i ), lda, t( 1, i ), ldt,
208 $ a( i, i+ib ), lda, work , n-i-ib+1 )
subroutine xerbla(srname, info)
subroutine sgeqrt2(m, n, a, lda, t, ldt, info)
SGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY represen...
recursive subroutine sgeqrt3(m, n, a, lda, t, ldt, info)
SGEQRT3 recursively computes a QR factorization of a general real or complex matrix using the compact...
subroutine sgeqrt(m, n, nb, a, lda, t, ldt, work, info)
SGEQRT
subroutine slarfb(side, trans, direct, storev, m, n, k, v, ldv, t, ldt, c, ldc, work, ldwork)
SLARFB applies a block reflector or its transpose to a general rectangular matrix.