This is the mail archive of the gcc-bugs@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[Bug middle-end/32176] New: ICE on valid: tree check: expected integer_cst, have plus_expr in int_cst_value, at tree.c:7720


reduced from CP2K (PR 29975)

gfortran -v
Using built-in specs.
Target: x86_64-unknown-linux-gnu
gcc version 4.3.0 20070531 (experimental)

gfortran -fprefetch-loop-arrays -O2 test.f90
test.f90: In function ?polint?:
test.f90:1: internal compiler error: tree check: expected integer_cst, have
plus_expr in int_cst_value, at tree.c:7720
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://gcc.gnu.org/bugs.html> for instructions.

  SUBROUTINE polint(xa,ya,n,x,y,dy)
    INTEGER, PARAMETER :: dp=KIND(0.0D0)
    INTEGER, INTENT(in)                      :: n
    REAL(dp), INTENT(in)                     :: ya(n), xa(n), x
    REAL(dp), INTENT(out)                    :: y, dy

    INTEGER                                  :: i, m, ns
    REAL(dp)                                 :: c(n), d(n), den, dif, dift, &
                                                ho, hp, w

!
!

    ns=1

    dif=ABS(x-xa(1))
    DO i = 1,n
      dift=ABS(x-xa(i))
      IF (dift.lt.dif) THEN
        ns=i
        dif=dift
      ENDIF
      c(i)=ya(i)
      d(i)=ya(i)
    END DO
    !
    y=ya(ns)
    ns=ns-1
    DO m = 1,n-1
      DO i = 1,n-m
        ho=xa(i)-x
        hp=xa(i+m)-x
        w=c(i+1)-d(i)
        den=ho-hp
        IF(den.eq.0.) STOP 'POLINT'
        den=w/den
        d(i)=hp*den
        c(i)=ho*den
      END DO
      IF (2*ns.lt.n-m)THEN
        dy=c(ns+1)
      ELSE
        dy=d(ns)
        ns=ns-1
      ENDIF
      y=y+dy
    END DO
!
    RETURN
  END SUBROUTINE polint


-- 
           Summary: ICE on valid: tree check: expected integer_cst, have
                    plus_expr in int_cst_value, at tree.c:7720
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: middle-end
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: jv244 at cam dot ac dot uk


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


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]