126 SUBROUTINE clarf1l( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
134 INTEGER INCV, LDC, M, N
138 COMPLEX C( LDC, * ), V( * ), WORK( * )
145 parameter( one = ( 1.0e+0, 0.0e+0 ),
146 $ zero = ( 0.0e+0, 0.0e+0 ) )
150 INTEGER I, J, LASTV, LASTC, FIRSTV
160 INTEGER ILACLR, ILACLC
161 EXTERNAL lsame, ilaclr, ilaclc
165 applyleft = lsame( side,
'L' )
168 IF( tau.NE.zero )
THEN
178 DO WHILE( lastv.GT.firstv .AND. v( i ).EQ.zero )
184 lastc = ilaclc(lastv, n, c, ldc)
187 lastc = ilaclr(m, lastv, c, ldc)
190 IF( lastc.EQ.0 )
THEN
197 IF( lastv.EQ.firstv )
THEN
201 CALL cscal( lastc, one - tau, c( lastv, 1 ), ldc )
206 CALL cgemv(
'Conjugate transpose', lastv - firstv, lastc,
207 $ one, c( firstv, 1 ), ldc, v( i ), incv, zero,
213 work( j ) = work( j ) + conjg( c( lastv, j ) )
219 c( lastv, j ) = c( lastv, j )
220 $ - tau * conjg( work( j ) )
225 CALL cgerc( lastv - firstv, lastc, -tau, v( i ), incv,
226 $ work, 1, c( firstv, 1 ), ldc)
232 IF( lastv.EQ.firstv )
THEN
236 CALL cscal( lastc, one - tau, c( 1, lastv ), 1 )
241 CALL cgemv(
'No transpose', lastc, lastv - firstv, one,
242 $ c( 1, firstv ), ldc, v( i ), incv, zero,
247 CALL caxpy( lastc, one, c( 1, lastv ), 1, work, 1 )
251 CALL caxpy( lastc, -tau, work, 1, c( 1, lastv ), 1 )
255 CALL cgerc( lastc, lastv - firstv, -tau, work, 1, v( i ),
256 $ incv, c( 1, firstv ), ldc )
subroutine clarf1l(side, m, n, v, incv, tau, c, ldc, work)
CLARF1L applies an elementary reflector to a general rectangular
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV