Skip to content

Commit

Permalink
fixing compilation errors due to not checking for lastc=0
Browse files Browse the repository at this point in the history
  • Loading branch information
jprhyne committed Jun 20, 2024
1 parent 5953353 commit 57b267c
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 8 deletions.
9 changes: 5 additions & 4 deletions SRC/dlarf1f.f
Original file line number Diff line number Diff line change
Expand Up @@ -175,15 +175,13 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
* .. Parameters ..
DOUBLE PRECISION ONE, ZERO
PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
INTEGER IONE
PARAMETER ( IONE = 1 )
* ..
* .. Local Scalars ..
LOGICAL APPLYLEFT
INTEGER I, LASTV, LASTC
* ..
* .. External Subroutines ..
EXTERNAL DGEMV, DGER
EXTERNAL DGEMV, DGER, DAXPY, DSCAL
* ..
* .. External Functions ..
LOGICAL LSAME
Expand Down Expand Up @@ -211,7 +209,7 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
! Look for the last non-zero row in V.
! Since we are assuming that V(1) = 1, and it is not stored, so we
! shouldn't access it.
DO WHILE( LASTV.GE.2 .AND. V( I ).EQ.ZERO )
DO WHILE( LASTV.GT.1 .AND. V( I ).EQ.ZERO )
LASTV = LASTV - 1
I = I - INCV
END DO
Expand All @@ -223,6 +221,9 @@ SUBROUTINE DLARF1F( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
LASTC = ILADLR(M, LASTV, C, LDC)
END IF
END IF
IF( LASTC.EQ.0 ) THEN
RETURN
END IF
IF( APPLYLEFT ) THEN
*
* Form H * C
Expand Down
7 changes: 3 additions & 4 deletions SRC/dlarf1l.f
Original file line number Diff line number Diff line change
Expand Up @@ -142,8 +142,6 @@ SUBROUTINE DLARF1L( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
* .. Parameters ..
DOUBLE PRECISION ONE, ZERO
PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
INTEGER IONE
PARAMETER ( IONE = 1 )
* ..
* .. Local Scalars ..
LOGICAL APPLYLEFT
Expand Down Expand Up @@ -184,8 +182,9 @@ SUBROUTINE DLARF1L( SIDE, M, N, V, INCV, TAU, C, LDC, WORK )
LASTC = ILADLR(M, LASTV, C, LDC)
END IF
END IF
! Note that lastc.eq.0 renders the BLAS operations null; no special
! case is needed at this level.
IF( LASTC.EQ.0 ) THEN
RETURN
END IF
IF( APPLYLEFT ) THEN
*
* Form H * C
Expand Down

0 comments on commit 57b267c

Please sign in to comment.