124 SUBROUTINE slarf1l( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
132 INTEGER INCV, LDC, M, N
136 REAL C( LDC, * ), V( * ), WORK( * )
143 parameter( one = 1.0e+0, zero = 0.0e+0 )
147 INTEGER I, LASTV, LASTC, FIRSTV
154 INTEGER ILASLR, ILASLC
155 EXTERNAL lsame, ilaslr, ilaslc
159 applyleft = lsame( side,
'L' )
162 IF( tau.NE.zero )
THEN
172 DO WHILE( lastv.GT.firstv .AND. v( i ).EQ.zero )
178 lastc = ilaslc(lastv, n, c, ldc)
181 lastc = ilaslr(m, lastv, c, ldc)
184 IF( lastc.EQ.0 )
THEN
191 IF( lastv.EQ.firstv )
THEN
195 CALL sscal( lastc, one - tau, c( lastv, 1 ), ldc )
200 CALL sgemv(
'Transpose', lastv - firstv, lastc, one,
201 $ c( firstv, 1 ), ldc, v( i ), incv, zero,
206 CALL saxpy( lastc, one, c( lastv, 1 ), ldc, work, 1 )
210 CALL saxpy( lastc, -tau, work, 1, c( lastv, 1 ), ldc )
214 CALL sger( lastv - firstv, lastc, -tau, v( i ), incv,
215 $ work, 1, c( firstv, 1 ), ldc)
221 IF( lastv.EQ.firstv )
THEN
225 CALL sscal( lastc, one - tau, c( 1, lastv ), 1 )
230 CALL sgemv(
'No transpose', lastc, lastv - firstv, one,
231 $ c( 1, firstv ), ldc, v( i ), incv, zero,
236 CALL saxpy( lastc, one, c( 1, lastv ), 1, work, 1 )
240 CALL saxpy( lastc, -tau, work, 1, c( 1, lastv ), 1 )
244 CALL sger( lastc, lastv - firstv, -tau, work, 1, v( i ),
245 $ incv, c( 1, firstv ), ldc )
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
subroutine slarf1l(side, m, n, v, incv, tau, c, ldc, work)
SLARF1L applies an elementary reflector to a general rectangular