 |
LAPACK
3.9.0
LAPACK: Linear Algebra PACKage
|
Go to the documentation of this file.
125 SUBROUTINE sgelqt( M, N, MB, A, LDA, T, LDT, WORK, INFO )
133 INTEGER INFO, LDA, LDT, M, N, MB
136 REAL A( LDA, * ), T( LDT, * ), WORK( * )
143 INTEGER I, IB, IINFO, K
155 ELSE IF( n.LT.0 )
THEN
157 ELSE IF( mb.LT.1 .OR. ( mb.GT.min(m,n) .AND. min(m,n).GT.0 ) )
THEN
159 ELSE IF( lda.LT.max( 1, m ) )
THEN
161 ELSE IF( ldt.LT.mb )
THEN
165 CALL xerbla(
'SGELQT', -info )
177 ib = min( k-i+1, mb )
181 CALL sgelqt3( ib, n-i+1, a(i,i), lda, t(1,i), ldt, iinfo )
186 CALL slarfb(
'R',
'N',
'F',
'R', m-i-ib+1, n-i+1, ib,
187 $ a( i, i ), lda, t( 1, i ), ldt,
188 $ a( i+ib, i ), lda, work , m-i-ib+1 )
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.
recursive subroutine sgelqt3(M, N, A, LDA, T, LDT, INFO)
SGELQT3
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 xerbla(SRNAME, INFO)
XERBLA
subroutine sgelqt(M, N, MB, A, LDA, T, LDT, WORK, INFO)
SGELQT