126 SUBROUTINE cgeqrt2( M, N, A, LDA, T, LDT, INFO )
133 INTEGER INFO, LDA, LDT, M, N
136 COMPLEX A( LDA, * ), T( LDT, * )
143 parameter( one = (1.0,0.0), zero = (0.0,0.0) )
159 ELSE IF( m.LT.n )
THEN
161 ELSE IF( lda.LT.max( 1, m ) )
THEN
163 ELSE IF( ldt.LT.max( 1, n ) )
THEN
167 CALL xerbla(
'CGEQRT2', -info )
177 CALL clarfg( m-i+1, a( i, i ), a( min( i+1, m ), i ), 1,
188 CALL cgemv(
'C',m-i+1, n-i, one, a( i, i+1 ), lda,
189 $ a( i, i ), 1, zero, t( 1, n ), 1 )
193 alpha = -conjg(t( i, 1 ))
194 CALL cgerc( m-i+1, n-i, alpha, a( i, i ), 1,
195 $ t( 1, n ), 1, a( i, i+1 ), lda )
207 CALL cgemv(
'C', m-i+1, i-1, alpha, a( i, 1 ), lda,
208 $ a( i, i ), 1, zero, t( 1, i ), 1 )
213 CALL ctrmv(
'U',
'N',
'N', i-1, t, ldt, t( 1, i ), 1 )
217 t( i, i ) = t( i, 1 )
subroutine xerbla(srname, info)
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
subroutine cgeqrt2(m, n, a, lda, t, ldt, info)
CGEQRT2 computes a QR factorization of a general real or complex matrix using the compact WY represen...
subroutine cgerc(m, n, alpha, x, incx, y, incy, a, lda)
CGERC
subroutine clarfg(n, alpha, x, incx, tau)
CLARFG generates an elementary reflector (Householder matrix).
subroutine ctrmv(uplo, trans, diag, n, a, lda, x, incx)
CTRMV