OSDN Git Service

* obj-c++.dg/comp-types-10.mm: XFAIL for ICE.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / pr28971.f90
1 ! { dg-do compile }
2 ! This caused an ICE for gfortrans of July 2006 vintage.  It was a regression
3 ! that "fixed" itself.  The cause and the fix are mysteries.  This test is intended
4 ! to signal any further regression, should it occur.
5 !
6 ! Contributed by Oskar Enoksson  <enok@lysator.liu.se>
7
8 SUBROUTINE BUG(A,B)
9   IMPLICIT NONE
10   
11   INTEGER   :: A
12   INTEGER   :: B(2)
13   
14   INTEGER, PARAMETER :: C(2) = (/ 1,2 /)
15   
16   WHERE (C(:).EQ.A)
17     B = -1
18   END WHERE
19 END SUBROUTINE BUG
20