public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
@ 2011-11-23 17:44 Joost.VandeVondele at mat dot ethz.ch
  2011-11-23 18:57 ` [Bug middle-end/51285] " dominiq at lps dot ens.fr
                   ` (9 more replies)
  0 siblings, 10 replies; 11+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2011-11-23 17:44 UTC (permalink / raw)
  To: gcc-bugs

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

             Bug #: 51285
           Summary: [4.7 Regression] internal compiler error: in
                    check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
    Classification: Unclassified
           Product: gcc
           Version: 4.7.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: middle-end
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: Joost.VandeVondele@mat.ethz.ch


gcc trunk (4.7.0 20111122) fails on the testcase below with

gfortran -O3 bug.f90 
bug.f90: In function ‘tiny_find’:
bug.f90:25:0: internal compiler error: in check_loop_closed_ssa_use, at
tree-ssa-loop-manip.c:422

> cat bug.f90 
   SUBROUTINE smm_dnn_4_10_10_1_1_2_1(A,B,C)
      REAL(KIND=KIND(0.0D0))   :: C(4,10), B(10,10), A(4,10)
      DO j=           1 ,          10 ,           2
      DO i=           1 ,           4 ,           1
      DO l=           1 ,          10 ,           1
        C(i+0,j+0)=C(i+0,j+0)+A(i+0,l+0)*B(l+0,j+0)
        C(i+0,j+1)=C(i+0,j+1)+A(i+0,l+0)*B(l+0,j+1)
      ENDDO 
      ENDDO 
      ENDDO 
    END SUBROUTINE
   SUBROUTINE smm_dnn_4_10_10_6_4_1_1(A,B,C)
      REAL(KIND=KIND(0.0D0))   :: C(4,10), B(10,10), A(4,10)
      DO l=           1 ,          10 ,           1
      DO j=           1 ,          10 ,           1
        C(i+0,j+0)=C(i+0,j+0)+A(i+0,l+0)*B(l+0,j+0)
      ENDDO 
      ENDDO 
    END SUBROUTINE
 FUNCTION TEST(X,A,B,C,N) RESULT(res)
    DO i=1,N
       CALL X(A,B,C)
    ENDDO
 END FUNCTION
  PROGRAM tiny_find
    INTEGER, PARAMETER :: M=4,N=10,K=10,Nmin=2
     REAL         :: timing(6,M,N,K), best_time, test
     INTERFACE
       SUBROUTINE X(A,B,C)
       END SUBROUTINE
     END INTERFACE
   PROCEDURE(X) :: smm_dnn_4_10_10_1_1_2_1
   PROCEDURE(X) :: smm_dnn_4_10_10_6_4_1_1
     Niter=MAX(1,CEILING(MIN(100000000.0D0,1*gflop/flops)))
     DO imin=1,Nmin
       timing(1,1,2,1)=        MIN(timing(1,1,2,1),&
             TEST(smm_dnn_4_10_10_1_1_2_1,A,B,C,Niter))
       timing(6,4,1,1)=        MIN(timing(6,4,1,1),&
             TEST(smm_dnn_4_10_10_6_4_1_1,A,B,C,Niter))
       write(6,'(4I4,F12.6,F12.3)') &
         6,4,5,1,flops*Niter/gflop/timing(6,4,5,1)
     DO i=1,M
     DO j=1,N
     DO l=1,K
        IF (timing(iloop,i,j,l)< best_time) THEN
        ENDIF
     ENDDO
     ENDDO
     ENDDO
     ENDDO
 END PROGRAM tiny_find


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
@ 2011-11-23 18:57 ` dominiq at lps dot ens.fr
  2011-11-23 19:59 ` Joost.VandeVondele at mat dot ethz.ch
                   ` (8 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2011-11-23 18:57 UTC (permalink / raw)
  To: gcc-bugs

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

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2011-11-23
     Ever Confirmed|0                           |1

--- Comment #1 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2011-11-23 18:47:29 UTC ---
r172430 is OK, 
r172608 gives the ICE. 
Note there is no ICE for builds configured with --enable-checking=release.


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
  2011-11-23 18:57 ` [Bug middle-end/51285] " dominiq at lps dot ens.fr
@ 2011-11-23 19:59 ` Joost.VandeVondele at mat dot ethz.ch
  2011-11-24 18:36 ` burnus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2011-11-23 19:59 UTC (permalink / raw)
  To: gcc-bugs

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

Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu.org

--- Comment #2 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 2011-11-23 19:28:34 UTC ---
In that range there is the following commit

http://gcc.gnu.org/viewcvs/trunk/gcc/fortran/trans-decl.c?r1=172307&r2=172604&pathrev=172604

It could be a coincidence, but this thing

-  /* Do not use procedures that have a procedure argument because this
-     can result in problems of multiple decls during inlining.  */

seems to hold. The ICE is removed with

gfortran -O3 -fno-inline-functions bug.f90


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
  2011-11-23 18:57 ` [Bug middle-end/51285] " dominiq at lps dot ens.fr
  2011-11-23 19:59 ` Joost.VandeVondele at mat dot ethz.ch
@ 2011-11-24 18:36 ` burnus at gcc dot gnu.org
  2011-11-24 19:46 ` Joost.VandeVondele at mat dot ethz.ch
                   ` (6 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: burnus at gcc dot gnu.org @ 2011-11-24 18:36 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2011-11-24 18:07:14 UTC ---
(In reply to comment #2)
> In that range there is the following commit
> http://gcc.gnu.org/viewcvs/trunk/gcc/fortran/trans-decl.c?r1=172307&r2=172604&pathrev=172604
> It could be a coincidence, but this thing
> -  /* Do not use procedures that have a procedure argument because this
> -     can result in problems of multiple decls during inlining.  */
> seems to hold. The ICE is removed with
> gfortran -O3 -fno-inline-functions bug.f90

I think it can well be that that commit exposes the bug as it removed a double
declaration for the same function. The removal should allow inlining. Thus,
that's in line with -fno-inline-functions "fixing" the issue on the trunk.
However, I doubt that the commit causes the bug.


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (2 preceding siblings ...)
  2011-11-24 18:36 ` burnus at gcc dot gnu.org
@ 2011-11-24 19:46 ` Joost.VandeVondele at mat dot ethz.ch
  2011-11-25 14:46 ` dominiq at lps dot ens.fr
                   ` (5 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: Joost.VandeVondele at mat dot ethz.ch @ 2011-11-24 19:46 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #4 from Joost VandeVondele <Joost.VandeVondele at mat dot ethz.ch> 2011-11-24 19:25:06 UTC ---
Simplified testcase showing Tobias patch is unrelated. Is this still triggered
by the same range ?

   SUBROUTINE smm_dnn_4_10_10_1_1_2_1(A,B,C)
      REAL   :: C(4,10), B(10,10), A(4,10)
      DO j=           1 ,          10 ,           2
      DO i=           1 ,           4 ,           1
      DO l=           1 ,          10 ,           1
        C(i+0,j+0)=C(i+0,j+0)+A(i+0,l+0)*B(l+0,j+0)
        C(i+0,j+1)=C(i+0,j+1)+A(i+0,l+0)*B(l+0,j+1)
      ENDDO 
      ENDDO 
      ENDDO 
    END SUBROUTINE
   SUBROUTINE smm_dnn_4_10_10_6_4_1_1(A,B,C)
      REAL   :: C(4,10), B(10,10), A(4,10)
      DO l=           1 ,          10 ,           1
      DO j=           1 ,          10 ,           1
        C(i+0,j+0)=C(i+0,j+0)+A(i+0,l+0)*B(l+0,j+0)
      ENDDO 
      ENDDO 
    END SUBROUTINE
 SUBROUTINE S(A,B,C)
    INTEGER :: Nmin=2,Niter=100
    REAL, DIMENSION(:,:), ALLOCATABLE   :: A,B,C
    DO imin=1,Nmin
     DO i=1,Niter
       CALL smm_dnn_4_10_10_1_1_2_1(A,B,C)
     ENDDO
     DO i=1,Niter
       CALL smm_dnn_4_10_10_6_4_1_1(A,B,C)
     ENDDO
     CALL foo()
    ENDDO
 END SUBROUTINE


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (3 preceding siblings ...)
  2011-11-24 19:46 ` Joost.VandeVondele at mat dot ethz.ch
@ 2011-11-25 14:46 ` dominiq at lps dot ens.fr
  2011-11-30  0:42 ` pinskia at gcc dot gnu.org
                   ` (4 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: dominiq at lps dot ens.fr @ 2011-11-25 14:46 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #5 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2011-11-25 14:08:23 UTC ---
> ... Is this still triggered by the same range ?

Yes.


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (4 preceding siblings ...)
  2011-11-25 14:46 ` dominiq at lps dot ens.fr
@ 2011-11-30  0:42 ` pinskia at gcc dot gnu.org
  2011-11-30 10:12 ` jakub at gcc dot gnu.org
                   ` (3 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: pinskia at gcc dot gnu.org @ 2011-11-30  0:42 UTC (permalink / raw)
  To: gcc-bugs

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

Andrew Pinski <pinskia at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Target Milestone|---                         |4.7.0


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (5 preceding siblings ...)
  2011-11-30  0:42 ` pinskia at gcc dot gnu.org
@ 2011-11-30 10:12 ` jakub at gcc dot gnu.org
  2011-12-04 10:51 ` irar at il dot ibm.com
                   ` (2 subsequent siblings)
  9 siblings, 0 replies; 11+ messages in thread
From: jakub at gcc dot gnu.org @ 2011-11-30 10:12 UTC (permalink / raw)
  To: gcc-bugs

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

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |irar at gcc dot gnu.org,
                   |                            |jakub at gcc dot gnu.org

--- Comment #6 from Jakub Jelinek <jakub at gcc dot gnu.org> 2011-11-30 08:42:47 UTC ---
Seems this ICEs during vectorization, a PHI created during
vect_create_epilog_for_reduction doesn't satisfy the closed loop SSA form
restrictions.


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (6 preceding siblings ...)
  2011-11-30 10:12 ` jakub at gcc dot gnu.org
@ 2011-12-04 10:51 ` irar at il dot ibm.com
  2011-12-04 14:52 ` irar at gcc dot gnu.org
  2011-12-05  9:42 ` jakub at gcc dot gnu.org
  9 siblings, 0 replies; 11+ messages in thread
From: irar at il dot ibm.com @ 2011-12-04 10:51 UTC (permalink / raw)
  To: gcc-bugs

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

Ira Rosen <irar at il dot ibm.com> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |ASSIGNED
         AssignedTo|unassigned at gcc dot       |irar at il dot ibm.com
                   |gnu.org                     |

--- Comment #7 from Ira Rosen <irar at il dot ibm.com> 2011-12-04 10:50:41 UTC ---
Created attachment 25985
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=25985
patch


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (7 preceding siblings ...)
  2011-12-04 10:51 ` irar at il dot ibm.com
@ 2011-12-04 14:52 ` irar at gcc dot gnu.org
  2011-12-05  9:42 ` jakub at gcc dot gnu.org
  9 siblings, 0 replies; 11+ messages in thread
From: irar at gcc dot gnu.org @ 2011-12-04 14:52 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #8 from irar at gcc dot gnu.org 2011-12-04 14:52:06 UTC ---
Author: irar
Date: Sun Dec  4 14:52:01 2011
New Revision: 181990

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=181990
Log:

        PR middle-end/51285
        * tree-vect-loop.c (vect_create_epilog_for_reduction): Create
        exit phi nodes for outer loop in case of double reduction.


Added:
    trunk/gcc/testsuite/gfortran.dg/vect/pr51285.f90
Modified:
    trunk/gcc/ChangeLog
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/tree-vect-loop.c


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

* [Bug middle-end/51285] [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c
  2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
                   ` (8 preceding siblings ...)
  2011-12-04 14:52 ` irar at gcc dot gnu.org
@ 2011-12-05  9:42 ` jakub at gcc dot gnu.org
  9 siblings, 0 replies; 11+ messages in thread
From: jakub at gcc dot gnu.org @ 2011-12-05  9:42 UTC (permalink / raw)
  To: gcc-bugs

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

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

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

--- Comment #9 from Jakub Jelinek <jakub at gcc dot gnu.org> 2011-12-05 09:41:31 UTC ---
Fixed.


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

end of thread, other threads:[~2011-12-05  9:42 UTC | newest]

Thread overview: 11+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-11-23 17:44 [Bug middle-end/51285] New: [4.7 Regression] internal compiler error: in check_loop_closed_ssa_use, at tree-ssa-loop-manip.c Joost.VandeVondele at mat dot ethz.ch
2011-11-23 18:57 ` [Bug middle-end/51285] " dominiq at lps dot ens.fr
2011-11-23 19:59 ` Joost.VandeVondele at mat dot ethz.ch
2011-11-24 18:36 ` burnus at gcc dot gnu.org
2011-11-24 19:46 ` Joost.VandeVondele at mat dot ethz.ch
2011-11-25 14:46 ` dominiq at lps dot ens.fr
2011-11-30  0:42 ` pinskia at gcc dot gnu.org
2011-11-30 10:12 ` jakub at gcc dot gnu.org
2011-12-04 10:51 ` irar at il dot ibm.com
2011-12-04 14:52 ` irar at gcc dot gnu.org
2011-12-05  9:42 ` jakub at gcc dot gnu.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).