123 SUBROUTINE sgelqt( M, N, MB, A, LDA, T, LDT, WORK, INFO )
130 INTEGER INFO, LDA, LDT, M, N, MB
133 REAL A( LDA, * ), T( LDT, * ), WORK( * )
140 INTEGER I, IB, IINFO, K
152 ELSE IF( n.LT.0 )
THEN
154 ELSE IF( mb.LT.1 .OR. ( mb.GT.min(m,n) .AND. min(m,n).GT.0 ) )
THEN
156 ELSE IF( lda.LT.max( 1, m ) )
THEN
158 ELSE IF( ldt.LT.mb )
THEN
162 CALL xerbla(
'SGELQT', -info )
174 ib = min( k-i+1, mb )
178 CALL sgelqt3( ib, n-i+1, a(i,i), lda, t(1,i), ldt, iinfo )
183 CALL slarfb(
'R',
'N',
'F',
'R', m-i-ib+1, n-i+1, ib,
184 $ a( i, i ), lda, t( 1, i ), ldt,
185 $ a( i+ib, i ), lda, work , m-i-ib+1 )
subroutine xerbla(srname, info)
recursive subroutine sgelqt3(m, n, a, lda, t, ldt, info)
SGELQT3
subroutine sgelqt(m, n, mb, a, lda, t, ldt, work, info)
SGELQT
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 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.