186 SUBROUTINE dgebd2( M, N, A, LDA, D, E, TAUQ, TAUP, WORK, INFO )
193 INTEGER INFO, LDA, M, N
196 DOUBLE PRECISION A( LDA, * ), D( * ), E( * ), TAUP( * ),
197 $ TAUQ( * ), WORK( * )
203 DOUBLE PRECISION ZERO
204 parameter( zero = 0.0d+0 )
222 ELSE IF( n.LT.0 )
THEN
224 ELSE IF( lda.LT.max( 1, m ) )
THEN
228 CALL xerbla(
'DGEBD2', -info )
240 CALL dlarfg( m-i+1, a( i, i ), a( min( i+1, m ), i ), 1,
247 $
CALL dlarf1f(
'Left', m-i+1, n-i, a( i, i ), 1,
249 $ a( i, i+1 ), lda, work )
256 CALL dlarfg( n-i, a( i, i+1 ), a( i, min( i+2, n ) ),
262 CALL dlarf1f(
'Right', m-i, n-i, a( i, i+1 ), lda,
263 $ taup( i ), a( i+1, i+1 ), lda, work )
276 CALL dlarfg( n-i+1, a( i, i ), a( i, min( i+1, n ) ),
284 $
CALL dlarf1f(
'Right', m-i, n-i+1, a( i, i ), lda,
285 $ taup( i ), a( i+1, i ), lda, work )
292 CALL dlarfg( m-i, a( i+1, i ), a( min( i+2, m ), i ),
299 CALL dlarf1f(
'Left', m-i, n-i, a( i+1, i ), 1,
301 $ a( i+1, i+1 ), lda, work )
subroutine dgebd2(m, n, a, lda, d, e, tauq, taup, work, info)
DGEBD2 reduces a general matrix to bidiagonal form using an unblocked algorithm.
subroutine dlarf1f(side, m, n, v, incv, tau, c, ldc, work)
DLARF1F applies an elementary reflector to a general rectangular
subroutine dlarfg(n, alpha, x, incx, tau)
DLARFG generates an elementary reflector (Householder matrix).