http://gcc.gnu.org/bugzilla/show_bug.cgi?id=54767



Richard Biener <rguenth at gcc dot gnu.org> changed:



           What    |Removed                     |Added

----------------------------------------------------------------------------

             Status|NEW                         |ASSIGNED

          Component|fortran                     |tree-optimization

         AssignedTo|unassigned at gcc dot       |rguenth at gcc dot gnu.org

                   |gnu.org                     |



--- Comment #8 from Richard Biener <rguenth at gcc dot gnu.org> 2013-01-15 
10:49:49 UTC ---

I don't see anything wrong by what VRP does:



Visiting statement:

prephitmp_2 = _79;



Found new range for prephitmp_2: [_79, _79]



Simulating statement (from ssa_edges): iaii_23 = PHI <iaii_1(11),

prephitmp_2(10)>



Visiting PHI node: iaii_23 = PHI <iaii_1(11), prephitmp_2(10)>



    Argument #0 (11 -> 12 executable)

        iaii_1

        Value: [_79, _79]



    Argument #1 (10 -> 12 executable)

        prephitmp_2

        Value: [_79, _79]  EQUIVALENCES: { _79 } (1 elements)

Meeting

  [_79, _79]

and

  [_79, _79]  EQUIVALENCES: { _79 } (1 elements)

to

  [_79, _79]

Found new range for iaii_23: [_79, _79]



Simulating statement (from ssa_edges): _35 = prephitmp_2 - iaii_23;



Visiting statement:

_35 = prephitmp_2 - iaii_23;



Found new range for _35: [0, 0]



Visiting statement:

ivvv.5_36 = _35 + 1;



Found new range for ivvv.5_36: [1, 1]





Now changed behavior is from:



Visiting PHI node: iaii_1 = PHI <iaii_18(D)(4), iaii_48(17)>



    Argument #0 (4 -> 5 executable)

        iaii_18(D)

        Value: UNDEFINED



    Argument #1 (17 -> 5 executable)

        iaii_48

        Value: [_79, _79]

Meeting

  UNDEFINED

and

  [_79, _79]

to

  [_79, _79]

Found new range for iaii_1: [_79, _79]



and this is all in a cycle.





I think this may be mixing _79 from different iterations.  Reduced testcase,

maybe easier to look at:



SUBROUTINE XXX (IL, IU)

  implicit none

  integer, INTENT(IN) :: IL, IU



  integer :: NXX (3) = (/ 0, 1, 2 /)

  integer :: ivvv, ia, ja, iaii

  logical :: qop



  QOP=.FALSE.



  DO IA=IL,IU

    JA=NXX(IA)

    IF (.NOT. QOP .and. JA.GT.0) THEN

      IAII=IA

      QOP=.TRUE.

    ENDIF



    IF (QOP) THEN

      ivvv=IA-IAII+1       ! mis-compiled

    ENDIF

  ENDDO



  IF (ivvv.NE.2) THEN

    call abort

  ENDIF

END subroutine



program p

  implicit none

  CALL XXX (1, 3)

end

Reply via email to