105 SUBROUTINE sget01( M, N, A, LDA, AFAC, LDAFAC, IPIV, RWORK,
113 INTEGER LDA, LDAFAC, M, N
118 REAL A( LDA, * ), AFAC( LDAFAC, * ), RWORK( * )
126 parameter( zero = 0.0e+0, one = 1.0e+0 )
133 REAL SDOT, SLAMCH, SLANGE
134 EXTERNAL sdot, slamch, slange
146 IF( m.LE.0 .OR. n.LE.0 )
THEN
153 eps = slamch(
'Epsilon' )
154 anorm = slange(
'1', m, n, a, lda, rwork )
162 CALL strmv(
'Lower',
'No transpose',
'Unit', m, afac,
163 $ ldafac, afac( 1, k ), 1 )
170 CALL sscal( m-k, t, afac( k+1, k ), 1 )
171 CALL sgemv(
'No transpose', m-k, k-1, one,
172 $ afac( k+1, 1 ), ldafac, afac( 1, k ), 1, one,
173 $ afac( k+1, k ), 1 )
178 afac( k, k ) = t + sdot( k-1, afac( k, 1 ), ldafac,
183 CALL strmv(
'Lower',
'No transpose',
'Unit', k-1, afac,
184 $ ldafac, afac( 1, k ), 1 )
187 CALL slaswp( n, afac, ldafac, 1, min( m, n ), ipiv, -1 )
193 afac( i, j ) = afac( i, j ) - a( i, j )
199 resid = slange(
'1', m, n, afac, ldafac, rwork )
201 IF( anorm.LE.zero )
THEN
205 resid = ( ( resid / real( n ) ) / anorm ) / eps
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
subroutine slaswp(n, a, lda, k1, k2, ipiv, incx)
SLASWP performs a series of row interchanges on a general rectangular matrix.
subroutine sscal(n, sa, sx, incx)
SSCAL
subroutine strmv(uplo, trans, diag, n, a, lda, x, incx)
STRMV
subroutine sget01(m, n, a, lda, afac, ldafac, ipiv, rwork, resid)
SGET01