------- Comment #5 from pault at gcc dot gnu dot org  2008-05-01 15:58 -------
This is now fixed on trunk and 4.3.  The following version of the big, original
testcase works fine.  If desired, it could be incorporated into the testsuite,
although I do not think that it adds anything.

Cheers

Paul

      MODULE MODS_big

! try this after you've fixed the two related problems.
! this is the full version of the parameters that spawned
! the smaller reports.  The ICE moved around and came and
! went as I tried to isolate things.  

! I believe there are two more ICEs in this set, but they're
! hard to isolate when things move around.

      INTEGER, PRIVATE, PARAMETER  ::
     $ np1 = 1, np2 = 2, NP6=6, NP7=7, NP8=8, NP9=9, NP10=10,
     $ MP6=-6, MP7=-7, MP8=-8, MP9=-9, MP10=-10, np5 = 5,
     $ mp1 = -1

      INTEGER, PARAMETER, DIMENSION(10) ::  IP_ARRAY1_1_M =
     $               (/1,2,3,4,5,6,7,8,9,10/)
      INTEGER, PARAMETER, DIMENSION(10) ::  IP_ARRAY1_2_M =
     $   (/(J1,J1=IP_ARRAY1_1_M(IP_ARRAY1_1_M(NP10)),NP1,MP1)/)

      INTEGER, DIMENSION(SIZE(IP_ARRAY1_1_M)/2) ::
     $     IP_ARRAY1_5_M = IP_ARRAY1_2_M(1:9:2)
      INTEGER, PARAMETER, DIMENSION(SIZE(IP_ARRAY1_1_M)/2) ::
     $     IP_ARRAY1_6_M = IP_ARRAY1_2_M(NP1:NP10:NP2)
      INTEGER, parameter, DIMENSION(10)  ::
     $   IP_ARRAY1_10_M = MAX(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_11_M = MIN(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_12_M = ABS(IP_ARRAY1_1_M-IP_ARRAY1_2_M),
     $   IP_ARRAY1_15_M = ((((DIM(((IP_ARRAY1_1_M)),IP_ARRAY1_2_M))))),
     $   IP_ARRAY1_17_M = IAND(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_18_M = IBCLR(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_19_M = IBITS(IP_ARRAY1_1_M,IP_ARRAY1_2_M,
     $                            MAX(3,IP_ARRAY1_2_M(10:1:-1))),
     $   IP_ARRAY1_20_M(-MP10) = IBSET(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_21_M(NP2*NP5) = IEOR(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_22_M(NP10) = IOR(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_23_M(10) = INT(IP_ARRAY1_1_M),
     $   IP_ARRAY1_24_M = ISHFT(IP_ARRAY1_1_M,IP_ARRAY1_2_M),
     $   IP_ARRAY1_25_M = ISHFTC(IP_ARRAY1_1_M,IP_ARRAY1_2_M,
     $                                     MAX(5,IP_ARRAY1_2_M))

      INTEGER, PARAMETER, DIMENSION(10) ::  I_ARRAY1_1_M =
     $               (/1,2,3,4,5,6,7,8,9,10/)
      INTEGER, PARAMETER, DIMENSION(10) ::  I_ARRAY1_2_M =
     $   (/(J1,J1=I_ARRAY1_1_M(I_ARRAY1_1_M(NP10)),NP1,MP1)/)

      INTEGER, DIMENSION(SIZE(I_ARRAY1_1_M)/2) ::
     $     I_ARRAY1_5_M = I_ARRAY1_2_M(1:9:2)
      INTEGER, PARAMETER, DIMENSION(SIZE(I_ARRAY1_1_M)/2) ::
     $     I_ARRAY1_6_M = I_ARRAY1_2_M(NP1:NP10:NP2)

      INTEGER, DIMENSION(10)  ::
     $   I_ARRAY1_10_M, 
     $   I_ARRAY1_11_M,
     $   I_ARRAY1_12_M,
     $   I_ARRAY1_15_M, 
     $   I_ARRAY1_17_M,
     $   I_ARRAY1_18_M,
     $   I_ARRAY1_19_M,
     $   I_ARRAY1_20_M(-MP10), 
     $   I_ARRAY1_21_M(NP2*NP5),
     $   I_ARRAY1_22_M(NP10),
     $   I_ARRAY1_23_M(10),
     $   I_ARRAY1_24_M,
     $   I_ARRAY1_25_M 


      END MODULE MODS_big

      use mods_big

C Do the variable assignments, using the library, to match the
C simplifications of the parameter initializations above.
      I_ARRAY1_10_M = MAX(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_11_M = MIN(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_12_M = ABS(I_ARRAY1_1_M-I_ARRAY1_2_M)
      I_ARRAY1_15_M = ((((DIM(((I_ARRAY1_1_M)),I_ARRAY1_2_M)))))
      I_ARRAY1_17_M = IAND(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_18_M = IBCLR(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_19_M = IBITS(I_ARRAY1_1_M,I_ARRAY1_2_M,
     $                      MAX(3,I_ARRAY1_2_M(10:1:-1)))
      I_ARRAY1_20_M = IBSET(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_21_M = IEOR(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_22_M = IOR(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_23_M = INT(I_ARRAY1_1_M)
      I_ARRAY1_24_M = ISHFT(I_ARRAY1_1_M,I_ARRAY1_2_M)
      I_ARRAY1_25_M = ISHFTC(I_ARRAY1_1_M,I_ARRAY1_2_M,
     $                       MAX(5,I_ARRAY1_2_M))

C Now do the comparisons.
      if (any (ip_array1_10_m .ne. i_array1_10_m)) call abort
      if (any (ip_array1_11_m .ne. i_array1_11_m)) call abort
      if (any (ip_array1_12_m .ne. i_array1_12_m)) call abort
      if (any (ip_array1_15_m .ne. i_array1_15_m)) call abort
      if (any (ip_array1_17_m .ne. i_array1_17_m)) call abort
      if (any (ip_array1_18_m .ne. i_array1_18_m)) call abort
      if (any (ip_array1_19_m .ne. i_array1_19_m)) call abort
      if (any (ip_array1_20_m .ne. i_array1_20_m)) call abort
      if (any (ip_array1_21_m .ne. i_array1_21_m)) call abort
      if (any (ip_array1_22_m .ne. i_array1_22_m)) call abort
      if (any (ip_array1_23_m .ne. i_array1_23_m)) call abort
      if (any (ip_array1_24_m .ne. i_array1_24_m)) call abort
      if (any (ip_array1_25_m .ne. i_array1_25_m)) call abort
      end


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED


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

Reply via email to