[Bug fortran/32931] New: FORALL and WHERE give an ICE with -fdefault-integer-8 and -m64

dominiq at lps dot ens dot fr gcc-bugzilla@gcc.gnu.org
Sun Jul 29 17:24:00 GMT 2007


I think the following is different enough from PR32770 to justify a new PR. As
reported,
gfortran.dg/forall_4.f90 and gfortran.dg/where_operator_assign_2.f90 give an
ICE
when compiled on darwin8 with both -fdefault-integer-8 and -m64 (see
PR32770#20) fo a backtrace. 

The following reduced codes yield the same ICE:

  integer, parameter :: n = 4
  integer :: i, a(n)
  logical :: s(n)
  s = .True.

  a = 0
  forall (i=1:n, .not. s(i)) a(i) = i
  if (any (a .ne. (/1,0,0,4/))) call abort ()

end

and

module global
  type :: a
    integer :: b
    integer :: c
  end type a
  interface assignment(=)
    module procedure a_to_a
  end interface
  interface operator(.ne.)
    module procedure a_ne_a
  end interface

  type(a) :: x(4), y(4), z(4), u(4, 4)
  logical :: l1(4), t = .true., f= .false.
contains
!******************************************************************************
  elemental subroutine a_to_a (m, n)
    type(a), intent(in) :: n
    type(a), intent(out) :: m
    m%b = n%b + 1
    m%c = n%c
  end subroutine a_to_a
!******************************************************************************
  elemental logical function a_ne_a (m, n)
    type(a), intent(in) :: n
    type(a), intent(in) :: m
    a_ne_a = (m%b .ne. n%b) .or. (m%c .ne. n%c)
  end function a_ne_a
!******************************************************************************
  elemental function foo (m)
    type(a) :: foo
    type(a), intent(in) :: m
    foo%b = 0
    foo%c = m%c
  end function foo  
end module global
!******************************************************************************
program test
  use global
  x = (/a (0, 1),a (0, 2),a (0, 3),a (0, 4)/)
  y = x
  z = x
  l1 = (/t, f, f, t/)

  call test_where_3
  if (any (y .ne. (/a (1, 0),a (1, 2),a (1, 3),a (1, 0)/))) call abort ()

!  y = x
!  call test_where_forall_1
!  if (any (u(4, :) .ne. (/a (1, 4),a (2, 2),a (2, 3),a (1, 4)/))) call abort
()

contains
!******************************************************************************
  subroutine test_where_3        ! Test a simple WHERE with a function
assignment
    where (.not. l1) y = foo (x)
  end subroutine test_where_3
!******************************************************************************
!  subroutine test_where_forall_1 ! Test a WHERE in a FORALL block
!    forall (i = 1:4)
!      where (.not. l1)
!        u(i, :) = x
!      elsewhere
!        u(i, :) = a(0, i)
!      endwhere
!    end forall
!  end subroutine test_where_forall_1
!******************************************************************************
end program test 

The commented FORALL also gives the same ICE. However the simplified version of
the last code:

program test
  integer :: x(4), y(4), z(4), u(4, 4)
  logical :: l1(4), t = .true., f= .false.
  x = (/ 1, 2, 3, 4/)
  l1 = (/t, f, f, t/)

  y = 0
  where (.not. l1) y = x
  if (any (y .ne. (/0, 2, 3, 0/))) call abort ()

end program test 

compiles and pass. Note also that the problem is also present in gcc 4.2.1.


-- 
           Summary: FORALL and WHERE give an ICE with -fdefault-integer-8
                    and -m64
           Product: gcc
           Version: 4.3.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: dominiq at lps dot ens dot fr
GCC target triplet: powerpc-apple-darwin8


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



More information about the Gcc-bugs mailing list