public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime
@ 2005-03-18 19:28 pinskia at gcc dot gnu dot org
  2005-03-18 22:24 ` [Bug fortran/20538] " kargl at gcc dot gnu dot org
                   ` (12 more replies)
  0 siblings, 13 replies; 14+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2005-03-18 19:28 UTC (permalink / raw)
  To: gcc-bugs

From:
<http://shootout.alioth.debian.org/great/benchmark.php?test=nbody&lang=g95&id=0&sort=fullcpu>

program nbody

  implicit none
  integer result, num, i, k
  character(len=8) argv
  real*8, parameter :: tstep = 0.01d0
  real*8, parameter ::  PI = 3.141592653589793d0
  real*8, parameter ::  SOLAR_MASS = 4 * PI * PI
  real*8, parameter ::  DAYS_PER_YEAR = 365.24d0
  real*8 :: e
  type body
     real*8 x, y, z, vx, vy, vz, mass
  end type body
  type(body), parameter :: jupiter = body( &
       4.84143144246472090d0,    -1.16032004402742839d0, &
       -1.03622044471123109d-01, 1.66007664274403694d-03 * DAYS_PER_YEAR, &
       7.69901118419740425d-03 * DAYS_PER_YEAR, -6.90460016972063023d-05 * DAYS_PER_YEAR, 
&
       9.54791938424326609d-04 * SOLAR_MASS)

  type(body), parameter :: saturn = body( &
       8.34336671824457987d+00, &
       4.12479856412430479d+00, &
       -4.03523417114321381d-01, &
       -2.76742510726862411d-03 * DAYS_PER_YEAR, &
       4.99852801234917238d-03 * DAYS_PER_YEAR, &
       2.30417297573763929d-05 * DAYS_PER_YEAR, &
       2.85885980666130812d-04 * SOLAR_MASS)

  type(body), parameter :: uranus = body( &
           1.28943695621391310d+01, &
           -1.51111514016986312d+01, &
           -2.23307578892655734d-01, &
           2.96460137564761618d-03 * DAYS_PER_YEAR, &
           2.37847173959480950d-03 * DAYS_PER_YEAR, &
           -2.96589568540237556d-05 * DAYS_PER_YEAR, &
           4.36624404335156298d-05 * SOLAR_MASS )

  type(body), parameter :: neptune = body( &
       1.53796971148509165d+01, &
       -2.59193146099879641d+01, &
       1.79258772950371181d-01, &
       2.68067772490389322d-03 * DAYS_PER_YEAR, &
       1.62824170038242295d-03 * DAYS_PER_YEAR, &
       -9.51592254519715870d-05 * DAYS_PER_YEAR, &
       5.15138902046611451d-05 * SOLAR_MASS)

  type(body), parameter :: sun = body(0.0d0, 0.0d0, 0.0d0, 0.0d0, 0.0d0, 0.0d0, SOLAR_MASS)

  type(body), dimension(5) :: bodies
  bodies = (/ sun, jupiter, saturn, uranus, neptune /)

  call getarg(1,argv)
  read(argv,*) num

  call offsetMomentum(1,bodies)
  e = energy(bodies)
  write(*,'(f12.9)') e
  do i=1,num
     call advance(tstep, bodies)
  end do
  e = energy(bodies)
  write(*,'(f12.9)') e

contains

  subroutine offsetMomentum(k, bodies)
    integer, intent(in) :: k
    type(body), dimension(:), intent(inout) :: bodies
    real*8 :: px, py, pz
    px = 0.0d0
    py = 0.0d0
    pz = 0.0d0
    do i=1,size(bodies)
       px = px + bodies(i)%vx * bodies(i)%mass;
       py = py + bodies(i)%vy * bodies(i)%mass;
       pz = pz + bodies(i)%vz * bodies(i)%mass;
    end do
    bodies(k)%vx = -px/SOLAR_MASS
    bodies(k)%vy = -py/SOLAR_MASS
    bodies(k)%vz = -pz/SOLAR_MASS
  end subroutine offsetMomentum


  subroutine advance(tstep, bodies)
  real*8, intent(in) :: tstep
  type(body), dimension(:), intent(inout) :: bodies

  real*8 dx, dy, dz, distance, mag
  integer i, j

  do i=1,size(bodies)
     do j=i+1,size(bodies)
        dx = bodies(i)%x - bodies(j)%x
        dy = bodies(i)%y - bodies(j)%y
        dz = bodies(i)%z - bodies(j)%z

        distance = sqrt(dx*dx + dy*dy + dz*dz)
        mag = tstep / (distance * distance * distance)

        bodies(i)%vx = bodies(i)%vx - dx * bodies(j)%mass * mag
        bodies(i)%vy =  bodies(i)%vy - dy * bodies(j)%mass * mag
        bodies(i)%vz =  bodies(i)%vz - dz * bodies(j)%mass * mag

        bodies(j)%vx = bodies(j)%vx + dx * bodies(i)%mass * mag
        bodies(j)%vy = bodies(j)%vy + dy * bodies(i)%mass * mag
        bodies(j)%vz = bodies(j)%vz + dz * bodies(i)%mass * mag
     end do
  end do

  do i=1,size(bodies)
     bodies(i)%x = bodies(i)%x + tstep * bodies(i)%vx
     bodies(i)%y = bodies(i)%y + tstep * bodies(i)%vy
     bodies(i)%z = bodies(i)%z + tstep * bodies(i)%vz
  end do

  end subroutine advance

  real*8 function energy(bodies)
    type(body), dimension(:), intent(in) :: bodies
    real*8 dx, dy, dz, distance
    integer i, j

    energy = 0.0d0
    do i=1,size(bodies)
       energy = energy + 0.5d0 * bodies(i)%mass *  &
            ( bodies(i)%vx * bodies(i)%vx + &
            bodies(i)%vy * bodies(i)%vy + &
            bodies(i)%vz * bodies(i)%vz)

       do j=i+1,size(bodies)
          dx = bodies(i)%x - bodies(j)%x
          dy = bodies(i)%y - bodies(j)%y
          dz = bodies(i)%z - bodies(j)%z
          distance = sqrt(dx*dx + dy*dy + dz*dz)
          energy = energy - (bodies(i)%mass * bodies(j)%mass) / distance;
       end do

    end do
  end function energy

end program nbody



I don't know where the problem is which is why I am just filing it.

run with 600000 as the agrument to the problem.  If someone will reduce this for me, it would be nice.

-- 
           Summary: compiling -finline-functions -O2 and we crash at runtime
           Product: gcc
           Version: 4.1.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P2
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: pinskia at gcc dot gnu dot org
                CC: gcc-bugs at gcc dot gnu dot org


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
@ 2005-03-18 22:24 ` kargl at gcc dot gnu dot org
  2005-03-18 22:36 ` kargl at gcc dot gnu dot org
                   ` (11 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: kargl at gcc dot gnu dot org @ 2005-03-18 22:24 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From kargl at gcc dot gnu dot org  2005-03-18 22:24 -------
It appears to be an optimization bug.  It compiles and runs with
"-O" and "-O -finline-functions".  It seg faults with "-O2".  The
-finline-functions appears to be unrelated to the seg fault.

-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
  2005-03-18 22:24 ` [Bug fortran/20538] " kargl at gcc dot gnu dot org
@ 2005-03-18 22:36 ` kargl at gcc dot gnu dot org
  2005-03-19  0:54 ` tobi at gcc dot gnu dot org
                   ` (10 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: kargl at gcc dot gnu dot org @ 2005-03-18 22:36 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From kargl at gcc dot gnu dot org  2005-03-18 22:36 -------
I added a "print *, size(bodies)" in the advance routine.  We have

troutmask:kargl[295] gfc -o jk -O2 jk.f90
troutmask:kargl[296] ./jk 1
-0.169075164
        -595
-0.169075164
troutmask:kargl[297] gfc -o jk -O jk.f90
troutmask:kargl[298] ./jk 1
-0.169075164
           5
-0.169074954

Note, the correct answer is 5, so it looks like -O2 is screwing up the 
size() function.


-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
  2005-03-18 22:24 ` [Bug fortran/20538] " kargl at gcc dot gnu dot org
  2005-03-18 22:36 ` kargl at gcc dot gnu dot org
@ 2005-03-19  0:54 ` tobi at gcc dot gnu dot org
  2005-03-19  1:35 ` tobi at gcc dot gnu dot org
                   ` (9 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-03-19  0:54 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-03-19 00:54 -------
Slightly reduced testcase, segfaults at -O2, runs with lower optimization. 
Removing any single statement leads to either illegal floating pointn numbers or
makes the segfault disappear:

  character(len=8) argv
  real*8, parameter :: tstep = 0.01d0
  real*8 :: e
  type body
     real*8 x, y,z,vx,vy,vz, mass
  end type body
  type(body), parameter :: jupiter = body(1d0, 1d0, 1d0, 1d0, 1d0, 1d0, 1d0 )
  type(body), parameter :: sun = body(0.0d0, 0.0d0, 0.0d0, 0.0d0, 0.0d0, 0.0d0,1d0)

  type(body), dimension(2) :: bodies
  bodies = (/ sun, jupiter/)
  argv = "1"
  read (argv,*) num

  call offsetMomentum(1,bodies)
  do i=1,num
     call advance(tstep, bodies)
  end do
  e = 0.
  print *, e

contains

  subroutine offsetMomentum(k, bodies)
    integer, intent(in) :: k
    type(body), dimension(:), intent(inout) :: bodies
    real*8 :: px, py, pz
    do i=1,size(bodies)
       px =  bodies(i)%vx * bodies(i)%mass;
    end do
    bodies(k)%vx = -px
  end subroutine offsetMomentum


  subroutine advance(tstep, bodies)
  real*8, intent(in) :: tstep
  type(body), dimension(:), intent(inout) :: bodies

  real*8 dx, dy, dz, distance, mag
  integer i, j

  i = 1; j = 2; mag = 1.
        dx = bodies(i)%x - bodies(j)%x
        bodies(i)%vx = bodies(i)%vx - dx * bodies(j)%mass * mag

        bodies(j)%vx = bodies(j)%vx + dx * bodies(i)%mass * mag
        bodies(j)%vy = bodies(j)%vy + dy * bodies(i)%mass * mag
        bodies(j)%vz = bodies(j)%vz + dz * bodies(i)%mass * mag

  do i=1,size(bodies)
     bodies(i)%x = bodies(i)%x + tstep * bodies(i)%vx
     bodies(i)%y = bodies(i)%y + tstep * bodies(i)%vy
     bodies(i)%z = bodies(i)%z + tstep * bodies(i)%vz
  end do

  end subroutine advance

  real*8 function energy(bodies)
    type(body), dimension(:), intent(in) :: bodies
    real*8 dx, dy, dz, distance
    integer i, j

    energy = 0.0d0
  end function energy

end

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|                            |1
   Last reconfirmed|0000-00-00 00:00:00         |2005-03-19 00:54:17
               date|                            |


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (2 preceding siblings ...)
  2005-03-19  0:54 ` tobi at gcc dot gnu dot org
@ 2005-03-19  1:35 ` tobi at gcc dot gnu dot org
  2005-03-19  1:42 ` pinskia at gcc dot gnu dot org
                   ` (8 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-03-19  1:35 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-03-19 01:35 -------
Further reduction: segfaults at -O2, runs at -O0.
  real vx(1)
  num=2
  do i=1,num
     call advance(vx)
  end do
contains
  subroutine advance(bodies)
    real, dimension(:)::bodies
    bodies = 1.0
  end subroutine advance
end

-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (3 preceding siblings ...)
  2005-03-19  1:35 ` tobi at gcc dot gnu dot org
@ 2005-03-19  1:42 ` pinskia at gcc dot gnu dot org
  2005-03-19  1:47 ` tobi at gcc dot gnu dot org
                   ` (7 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2005-03-19  1:42 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From pinskia at gcc dot gnu dot org  2005-03-19 01:42 -------
This might be the same as PR 16898.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
  BugsThisDependsOn|                            |16898


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (4 preceding siblings ...)
  2005-03-19  1:42 ` pinskia at gcc dot gnu dot org
@ 2005-03-19  1:47 ` tobi at gcc dot gnu dot org
  2005-03-19  1:57 ` tobi at gcc dot gnu dot org
                   ` (6 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-03-19  1:47 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-03-19 01:47 -------
The failure is dependent on the function being a nested function, the following
doesn't segfault at -O2:
  subroutine advance(bodies)
    real, dimension(:)::bodies
    bodies = 1.0
  end subroutine advance
interface
  subroutine advance(bodies)
    real, dimension(:)::bodies
  end subroutine advance
end interface
  real vx(1)
  num=2
  do i=1,num
     call advance(vx)
  end do
end


-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (5 preceding siblings ...)
  2005-03-19  1:47 ` tobi at gcc dot gnu dot org
@ 2005-03-19  1:57 ` tobi at gcc dot gnu dot org
  2005-03-19  1:59 ` pbrook at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-03-19  1:57 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-03-19 01:57 -------
This modified testcase which removes the nested function, fails at -O2 by giving
******** as output, but works at -O0. I'm not sure if this is a different
manifestation of the same bug, so I'm putting this here as something to look at
once this PR is fixed.

module m
  type body
     real*8 x, y, z, vx, vy, vz, mass
  end type body
contains
  subroutine offsetMomentum(k, bodies)
    integer, intent(in) :: k
    type(body), dimension(:), intent(inout) :: bodies
    real*8 :: px, py, pz
    px = 0.0d0
    py = 0.0d0
    pz = 0.0d0
    do i=1,size(bodies)
       px = px + bodies(i)%vx * bodies(i)%mass;
       py = py + bodies(i)%vy * bodies(i)%mass;
       pz = pz + bodies(i)%vz * bodies(i)%mass;
    end do
    bodies(k)%vx = -px/SOLAR_MASS
    bodies(k)%vy = -py/SOLAR_MASS
    bodies(k)%vz = -pz/SOLAR_MASS
  end subroutine offsetMomentum


  subroutine advance(tstep, bodies)
  real*8, intent(in) :: tstep
  type(body), dimension(:), intent(inout) :: bodies

  real*8 dx, dy, dz, distance, mag
  integer i, j

  do i=1,size(bodies)
     do j=i+1,size(bodies)
        dx = bodies(i)%x - bodies(j)%x
        dy = bodies(i)%y - bodies(j)%y
        dz = bodies(i)%z - bodies(j)%z

        distance = sqrt(dx*dx + dy*dy + dz*dz)
        mag = tstep / (distance * distance * distance)

        bodies(i)%vx = bodies(i)%vx - dx * bodies(j)%mass * mag
        bodies(i)%vy =  bodies(i)%vy - dy * bodies(j)%mass * mag
        bodies(i)%vz =  bodies(i)%vz - dz * bodies(j)%mass * mag

        bodies(j)%vx = bodies(j)%vx + dx * bodies(i)%mass * mag
        bodies(j)%vy = bodies(j)%vy + dy * bodies(i)%mass * mag
        bodies(j)%vz = bodies(j)%vz + dz * bodies(i)%mass * mag
     end do
  end do

  do i=1,size(bodies)
     bodies(i)%x = bodies(i)%x + tstep * bodies(i)%vx
     bodies(i)%y = bodies(i)%y + tstep * bodies(i)%vy
     bodies(i)%z = bodies(i)%z + tstep * bodies(i)%vz
  end do

  end subroutine advance

  real*8 function energy(bodies)
    type(body), dimension(:), intent(in) :: bodies
    real*8 dx, dy, dz, distance
    integer i, j

    energy = 0.0d0
    do i=1,size(bodies)
       energy = energy + 0.5d0 * bodies(i)%mass *  &
            ( bodies(i)%vx * bodies(i)%vx + &
            bodies(i)%vy * bodies(i)%vy + &
            bodies(i)%vz * bodies(i)%vz)

       do j=i+1,size(bodies)
          dx = bodies(i)%x - bodies(j)%x
          dy = bodies(i)%y - bodies(j)%y
          dz = bodies(i)%z - bodies(j)%z
          distance = sqrt(dx*dx + dy*dy + dz*dz)
          energy = energy - (bodies(i)%mass * bodies(j)%mass) / distance;
       end do

    end do
  end function energy

  subroutine main
  implicit none

  integer result, num, i, k
  character(len=8) argv
  real*8, parameter :: tstep = 0.01d0
  real*8, parameter ::  PI = 3.141592653589793d0
  real*8, parameter ::  SOLAR_MASS = 4 * PI * PI
  real*8, parameter ::  DAYS_PER_YEAR = 365.24d0
  real*8 :: e
  type(body), parameter :: jupiter = body( &
       4.84143144246472090d0,    -1.16032004402742839d0, &
       -1.03622044471123109d-01, 1.66007664274403694d-03 * DAYS_PER_YEAR, &
       7.69901118419740425d-03 * DAYS_PER_YEAR, -6.90460016972063023d-05 *
DAYS_PER_YEAR, &
       9.54791938424326609d-04 * SOLAR_MASS)

  type(body), parameter :: saturn = body( &
       8.34336671824457987d+00, &
       4.12479856412430479d+00, &
       -4.03523417114321381d-01, &
       -2.76742510726862411d-03 * DAYS_PER_YEAR, &
       4.99852801234917238d-03 * DAYS_PER_YEAR, &
       2.30417297573763929d-05 * DAYS_PER_YEAR, &
       2.85885980666130812d-04 * SOLAR_MASS)

  type(body), parameter :: uranus = body( &
           1.28943695621391310d+01, &
           -1.51111514016986312d+01, &
           -2.23307578892655734d-01, &
           2.96460137564761618d-03 * DAYS_PER_YEAR, &
           2.37847173959480950d-03 * DAYS_PER_YEAR, &
           -2.96589568540237556d-05 * DAYS_PER_YEAR, &
           4.36624404335156298d-05 * SOLAR_MASS )

  type(body), parameter :: neptune = body( &
       1.53796971148509165d+01, &
       -2.59193146099879641d+01, &
       1.79258772950371181d-01, &
       2.68067772490389322d-03 * DAYS_PER_YEAR, &
       1.62824170038242295d-03 * DAYS_PER_YEAR, &
       -9.51592254519715870d-05 * DAYS_PER_YEAR, &
       5.15138902046611451d-05 * SOLAR_MASS)

  type(body), parameter :: sun = body(0.0d0, 0.0d0, 0.0d0, 0.0d0, 0.0d0, 0.0d0,
SOLAR_MASS)

  type(body), dimension(5) :: bodies
  bodies = (/ sun, jupiter, saturn, uranus, neptune /)

  argv = "6000"
  read(argv,*) num

  call offsetMomentum(1,bodies)
  e = energy(bodies)
  write(*,'(f12.9)') e
  do i=1,num
     call advance(tstep, bodies)
  end do
  e = energy(bodies)
  write(*,'(f12.9)') e
end subroutine main
end module m

use m
call main
end


-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (6 preceding siblings ...)
  2005-03-19  1:57 ` tobi at gcc dot gnu dot org
@ 2005-03-19  1:59 ` pbrook at gcc dot gnu dot org
  2005-03-19 12:08 ` tobi at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: pbrook at gcc dot gnu dot org @ 2005-03-19  1:59 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From pbrook at gcc dot gnu dot org  2005-03-19 01:58 -------
Due to general gfortran lameness only contained functions are ever inlined.  
Top-level functions are never inlined.  

-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (7 preceding siblings ...)
  2005-03-19  1:59 ` pbrook at gcc dot gnu dot org
@ 2005-03-19 12:08 ` tobi at gcc dot gnu dot org
  2005-03-19 13:20 ` Thomas dot Koenig at online dot de
                   ` (3 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-03-19 12:08 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-03-19 11:51 -------
One further reduction, still the same misbehavior:
  real vx(1)
  num=2
  do i=1,num
     call advance(vx)
  end do
contains
  subroutine advance(bodies)
    real, dimension(:)::bodies
    bodies(1) = 1.0
  end subroutine advance
end
gives the following, correct looking, .optimized dump:

;; Function MAIN__ (MAIN__)

Analyzing Edge Insertions.
MAIN__ ()
{
  <unnamed type> ivtmp.13;
  int4 prephitmp.12;
  int4 pretmp.11;
  int4 pretmp.10;
  struct array1_real4 & pretmp.9;
  real4[0:] * pretmp.8;
  int4 D.520;
  real4[0:] * bodies.0;
  int4 offset.2;
  int4 stride.1;
  int4 ubound.0;
  int4 D.519;
  int4 D.518;
  int4 D.517;
  int4 D.516;
  real4[0:] * D.515;
  int4 iftmp.4;
  struct array1_real4 & bodies;
  struct array1_real4 parm.3;
  logical4 D.499;
  int4 D.490;
  real4 vx[1];
  int4 i;
  int4 num;
  real4[0:] * D.501;

<bb 0>:
  pretmp.8 = (real4[0:] *) &vx[0];
  pretmp.9 = (struct array1_real4 &) &parm.3;
  i = 1;

<L0>:;
  parm.3.dtype = 281;
  parm.3.dim[0].lbound = 1;
  parm.3.dim[0].ubound = 1;
  parm.3.dim[0].stride = 1;
  parm.3.data = pretmp.8;
  parm.3.offset = 0;
  stride.1 = pretmp.9->dim[0].stride;
  if (stride.1 == 0) goto <L12>; else goto <L10>;

<L12>:;
  stride.1 = 1;
  prephitmp.12 = -1;
  goto <bb 3> (<L4>);

<L10>:;
  prephitmp.12 = -stride.1;

<L4>:;
  (*(real4[0:] *) pretmp.9->data)[stride.1 + prephitmp.12] = 1.0e+0;
  if (i == 2) goto <L7>; else goto <L11>;

<L11>:;
  i = i + 1;
  goto <bb 1> (<L0>);

<L7>:;
  return;

}


With -fno-strict-aliasing the testcase doesn't segfault any longer.  The
differences in the .optimized dump are this:
--- pr20538.f90.t67.optimized   2005-03-19 12:46:23.472057734 +0100
+++ pr20538.f90.t67.optimized.no-strict 2005-03-19 12:45:56.000775891 +0100
@@ -4,12 +4,12 @@
 Analyzing Edge Insertions.
 MAIN__ ()
 {
-  <unnamed type> ivtmp.13;
-  int4 prephitmp.12;
-  int4 pretmp.11;
+  <unnamed type> ivtmp.12;
+  int4 prephitmp.11;
   int4 pretmp.10;
-  struct array1_real4 & pretmp.9;
-  real4[0:] * pretmp.8;
+  int4 pretmp.9;
+  struct array1_real4 & pretmp.8;
+  real4[0:] * pretmp.7;
   int4 D.520;
   real4[0:] * bodies.0;
   int4 offset.2;
@@ -31,8 +31,8 @@ MAIN__ ()
   real4[0:] * D.501;

 <bb 0>:
-  pretmp.8 = (real4[0:] *) &vx[0];
-  pretmp.9 = (struct array1_real4 &) &parm.3;
+  pretmp.7 = (real4[0:] *) &vx[0];
+  pretmp.8 = (struct array1_real4 &) &parm.3;
   i = 1;

 <L0>:;
@@ -40,21 +40,21 @@ MAIN__ ()
   parm.3.dim[0].lbound = 1;
   parm.3.dim[0].ubound = 1;
   parm.3.dim[0].stride = 1;
-  parm.3.data = pretmp.8;
+  parm.3.data = pretmp.7;
   parm.3.offset = 0;
-  stride.1 = pretmp.9->dim[0].stride;
+  stride.1 = pretmp.8->dim[0].stride;
   if (stride.1 == 0) goto <L12>; else goto <L10>;

 <L12>:;
   stride.1 = 1;
-  prephitmp.12 = -1;
+  prephitmp.11 = -1;
   goto <bb 3> (<L4>);

 <L10>:;
-  prephitmp.12 = -stride.1;
+  prephitmp.11 = -stride.1;

 <L4>:;
-  (*(real4[0:] *) pretmp.9->data)[stride.1 + prephitmp.12] = 1.0e+0;
+  (*(real4[0:] *) pretmp.8->data)[stride.1 + prephitmp.11] = 1.0e+0;
   if (i == 2) goto <L7>; else goto <L11>;

 <L11>:;

i.e. only a few temporaries got renamed in all places where they're used.

-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (8 preceding siblings ...)
  2005-03-19 12:08 ` tobi at gcc dot gnu dot org
@ 2005-03-19 13:20 ` Thomas dot Koenig at online dot de
  2005-03-19 13:24 ` pinskia at gcc dot gnu dot org
                   ` (2 subsequent siblings)
  12 siblings, 0 replies; 14+ messages in thread
From: Thomas dot Koenig at online dot de @ 2005-03-19 13:20 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From Thomas dot Koenig at online dot de  2005-03-19 13:20 -------
(In reply to comment #8)

> Due to general gfortran lameness only contained functions are ever inlined.  
> Top-level functions are never inlined.  

Why?

I've worked with a Fortrtran 77 compiler (vor the Fujitsu VP series
of vector computers) that did inline subroutines if they apppeared
previously in the source code.


-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (9 preceding siblings ...)
  2005-03-19 13:20 ` Thomas dot Koenig at online dot de
@ 2005-03-19 13:24 ` pinskia at gcc dot gnu dot org
  2005-05-18 21:23 ` tobi at gcc dot gnu dot org
  2005-06-04 21:00 ` tobi at gcc dot gnu dot org
  12 siblings, 0 replies; 14+ messages in thread
From: pinskia at gcc dot gnu dot org @ 2005-03-19 13:24 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From pinskia at gcc dot gnu dot org  2005-03-19 13:24 -------
(In reply to comment #10)
> (In reply to comment #8)
> 
> > Due to general gfortran lameness only contained functions are ever inlined.  
> > Top-level functions are never inlined.  
> 
> Why?
I think Paul means that the front-end is wrong (and is a bug) in that it will not allow the inlining of top 
level functions.  

-- 


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (10 preceding siblings ...)
  2005-03-19 13:24 ` pinskia at gcc dot gnu dot org
@ 2005-05-18 21:23 ` tobi at gcc dot gnu dot org
  2005-06-04 21:00 ` tobi at gcc dot gnu dot org
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-05-18 21:23 UTC (permalink / raw)
  To: gcc-bugs


------- Additional Comments From tobi at gcc dot gnu dot org  2005-05-18 21:23 -------
This is fixed by Zdenek recent fix for aliasing issues.  I'm setting the target
milestone to 4.1, but if Zdenek applies his patch to 4.0 this should probably be
changed as well.

-- 
           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|                            |FIXED
   Target Milestone|---                         |4.1.0


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


^ permalink raw reply	[flat|nested] 14+ messages in thread

* [Bug fortran/20538] compiling -finline-functions -O2 and we crash at runtime
  2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
                   ` (11 preceding siblings ...)
  2005-05-18 21:23 ` tobi at gcc dot gnu dot org
@ 2005-06-04 21:00 ` tobi at gcc dot gnu dot org
  12 siblings, 0 replies; 14+ messages in thread
From: tobi at gcc dot gnu dot org @ 2005-06-04 21:00 UTC (permalink / raw)
  To: gcc-bugs



-- 
Bug 20538 depends on bug 16898, which changed state.

Bug 16898 Summary: Aliasing problem with array descriptors
http://gcc.gnu.org/bugzilla/show_bug.cgi?id=16898

           What    |Old Value                   |New Value
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|                            |FIXED

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


^ permalink raw reply	[flat|nested] 14+ messages in thread

end of thread, other threads:[~2005-06-04 21:00 UTC | newest]

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2005-03-18 19:28 [Bug fortran/20538] New: compiling -finline-functions -O2 and we crash at runtime pinskia at gcc dot gnu dot org
2005-03-18 22:24 ` [Bug fortran/20538] " kargl at gcc dot gnu dot org
2005-03-18 22:36 ` kargl at gcc dot gnu dot org
2005-03-19  0:54 ` tobi at gcc dot gnu dot org
2005-03-19  1:35 ` tobi at gcc dot gnu dot org
2005-03-19  1:42 ` pinskia at gcc dot gnu dot org
2005-03-19  1:47 ` tobi at gcc dot gnu dot org
2005-03-19  1:57 ` tobi at gcc dot gnu dot org
2005-03-19  1:59 ` pbrook at gcc dot gnu dot org
2005-03-19 12:08 ` tobi at gcc dot gnu dot org
2005-03-19 13:20 ` Thomas dot Koenig at online dot de
2005-03-19 13:24 ` pinskia at gcc dot gnu dot org
2005-05-18 21:23 ` tobi at gcc dot gnu dot org
2005-06-04 21:00 ` tobi at gcc dot gnu dot org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).