Skip to content

Commit 741907c

Browse files
committed
updating dlarf1f and dlarf1l to fix a bug found within dorg2l
1 parent 7708f1e commit 741907c

File tree

3 files changed

+5
-11
lines changed

3 files changed

+5
-11
lines changed

SRC/dlarf1f.f

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -211,7 +211,7 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
211211
! Look for the last non-zero row in V.
212212
! Since we are assuming that V(1) = 1, and it is not stored, so we
213213
! shouldn't access it.
214-
DO WHILE( LASTV.GT.1 .AND. V( I ).EQ.ZERO )
214+
DO WHILE( LASTV.GE.2 .AND. V( I ).EQ.ZERO )
215215
LASTV = LASTV - 1
216216
I = I - INCV
217217
END DO
@@ -232,7 +232,7 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
232232
*
233233
! Check if lastv = 1. This means v = 1, So we just need to compute
234234
! C := HC = (1-\tau)C.
235-
IF( LASTV.EQ.1 ) THEN
235+
IF( LASTV.LE.1 ) THEN
236236
CALL DSCAL(LASTC, ONE - TAU, C, LDC)
237237
ELSE
238238
*

SRC/dlarf1l.f

Lines changed: 2 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -170,23 +170,16 @@ SUBROUTINE DLARF1L( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
170170
ELSE
171171
LASTV = N
172172
END IF
173-
IF( INCV.GT.0 ) THEN
174-
I = 1 + (LASTV-1) * INCV
175-
ELSE
176-
I = 1
177-
END IF
178173
! Look for the last non-zero row in V.
179-
DO WHILE( LASTV.GT.0 .AND. V( I ).EQ.ZERO )
180-
LASTV = LASTV - 1
181-
I = I - INCV
182-
END DO
183174
IF( APPLYLEFT ) THEN
184175
! Scan for the last non-zero column in C(1:lastv,:).
185176
LASTC = ILADLC(LASTV, N, C, LDC)
186177
ELSE
187178
! Scan for the last non-zero row in C(:,1:lastv).
188179
LASTC = ILADLR(M, LASTV, C, LDC)
189180
END IF
181+
ELSE
182+
RETURN
190183
END IF
191184
! Note that lastc.eq.0 renders the BLAS operations null; no special
192185
! case is needed at this level.

SRC/dorg2l.f

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -176,6 +176,7 @@ SUBROUTINE DORG2L( M, N, K, A, LDA, TAU, WORK, INFO )
176176
*
177177
* Apply H(i) to A(1:m-k+i,1:n-k+i) from the left
178178
*
179+
!A(M-N+II, II) = ONE
179180
CALL DLARF1L( 'Left', M-N+II, II-1, A( 1, II ), 1, TAU( I ),
180181
$ A,
181182
$ LDA, WORK )

0 commit comments

Comments
 (0)