129 SUBROUTINE zlarf1l( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
137 INTEGER INCV, LDC, M, N
141 COMPLEX*16 C( LDC, * ), V( * ), WORK( * )
148 parameter( one = ( 1.0d+0, 0.0d+0 ),
149 $ zero = ( 0.0d+0, 0.0d+0 ) )
153 INTEGER I, J, LASTV, LASTC, FIRSTV
163 INTEGER ILAZLR, ILAZLC
164 EXTERNAL lsame, ilazlr, ilazlc
168 applyleft = lsame( side,
'L' )
171 IF( tau.NE.zero )
THEN
181 DO WHILE( lastv.GT.firstv .AND. v( i ).EQ.zero )
187 lastc = ilazlc(lastv, n, c, ldc)
190 lastc = ilazlr(m, lastv, c, ldc)
193 IF( lastc.EQ.0 )
THEN
200 IF( lastv.EQ.firstv )
THEN
204 CALL zscal( lastc, one - tau, c( lastv, 1 ), ldc )
209 CALL zgemv(
'Conjugate transpose', lastv - firstv, lastc,
210 $ one, c( firstv, 1 ), ldc, v( i ), incv, zero,
216 work( j ) = work( j ) + conjg( c( lastv, j ) )
222 c( lastv, j ) = c( lastv, j )
223 $ - tau * conjg( work( j ) )
228 CALL zgerc( lastv - firstv, lastc, -tau, v( i ), incv,
229 $ work, 1, c( firstv, 1 ), ldc)
235 IF( lastv.EQ.firstv )
THEN
239 CALL zscal( lastc, one - tau, c( 1, lastv ), 1 )
244 CALL zgemv(
'No transpose', lastc, lastv - firstv, one,
245 $ c( 1, firstv ), ldc, v( i ), incv, zero,
250 CALL zaxpy( lastc, one, c( 1, lastv ), 1, work, 1 )
254 CALL zaxpy( lastc, -tau, work, 1, c( 1, lastv ), 1 )
258 CALL zgerc( lastc, lastv - firstv, -tau, work, 1, v( i ),
259 $ incv, c( 1, firstv ), ldc )
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
subroutine zlarf1l(side, m, n, v, incv, tau, c, ldc, work)
ZLARF1L applies an elementary reflector to a general rectangular