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

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).