public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/36114]  New: [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867
@ 2008-05-02 22:30 dominiq at lps dot ens dot fr
  2008-05-03  9:12 ` [Bug fortran/36114] " rguenth at gcc dot gnu dot org
                   ` (3 more replies)
  0 siblings, 4 replies; 5+ messages in thread
From: dominiq at lps dot ens dot fr @ 2008-05-02 22:30 UTC (permalink / raw)
  To: gcc-bugs

The following codes from pr29921 and pr35770:

ibook-dhum] f90/bug% cat pr29921.f90
! { dg-do compile }
      SUBROUTINE foo
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      LOGICAL MASWRK
      COMMON /FRAME / W1,W2,W3
      COMMON /FRAMES/ X1,Y1,Z1,X2,Y2,Z2,X3,Y3,Z3
      PARAMETER (ZERO=0.0D+00, ONE=1.0D+00)
      IF (IGROUP .EQ. 1) GO TO 600
      IF (IGROUP .EQ. 2) GO TO 620
  600 NT = 1
  620 CONTINUE
      IF (RHO .GT. TOL) THEN
         Y3 = RFIND('Y3      ',IERR)
            IF(IERR.NE.0) CALL ABRT
         Z3 = RFIND('Z3      ',IERR)
            IF(IERR.NE.0) CALL ABRT
         IF (MASWRK) WRITE (IP,9048) X3,Y3,Z3
      ELSE
         X1 = ZERO
         Y1 = ZERO
         Z1 = ZERO
         Z3 = ZERO
         X2 = ONE
         Y3 = ONE
      END IF
      W2 = (Z2-Z1)*(X3-X1)-(Z3-Z1)*(X2-X1)
 9048 FORMAT(9F10.5)
      END
[ibook-dhum] f90/bug% cat pr35770.f90
! fails on Windows XP
! gcc version 4.4.0 20080312 (experimental) [trunk revision 133139]
!maybe also see 34784?


      implicit character (s)  ! removing this fixes the problem
      REAL RDA(10)
      RDA = 0

      RDA(J1) = S_REAL_SQRT_I(RDA(J1))

      CONTAINS

      ELEMENTAL FUNCTION S_REAL_SQRT_I(X) RESULT (R)
      REAL, INTENT(IN)  ::  X
      REAL              ::  R
        R = 0.0
      END FUNCTION S_REAL_SQRT_I     !internal procedure

      END

gives "f951: internal compiler error: Bus error" after revision 134867. The bus
errors disappear if I revert the revision, while pr35770 gives:

      RDA(J1) = S_REAL_SQRT_I(RDA(J1))
               1
Error: Can't convert CHARACTER(1) to REAL(4) at (1)


-- 
           Summary: [4.4 Regression] "f951: internal compiler error: Bus
                    error" due to revision 134867
           Product: gcc
           Version: 4.4.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 build triplet: *-apple-darwin9
  GCC host triplet: *-apple-darwin9
GCC target triplet: *-apple-darwin9


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


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

* [Bug fortran/36114] [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867
  2008-05-02 22:30 [Bug fortran/36114] New: [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867 dominiq at lps dot ens dot fr
@ 2008-05-03  9:12 ` rguenth at gcc dot gnu dot org
  2008-05-03 20:12 ` jaydub66 at gmail dot com
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 5+ messages in thread
From: rguenth at gcc dot gnu dot org @ 2008-05-03  9:12 UTC (permalink / raw)
  To: gcc-bugs



-- 

rguenth at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |jaydub66 at gmail dot com
   Target Milestone|---                         |4.4.0


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


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

* [Bug fortran/36114] [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867
  2008-05-02 22:30 [Bug fortran/36114] New: [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867 dominiq at lps dot ens dot fr
  2008-05-03  9:12 ` [Bug fortran/36114] " rguenth at gcc dot gnu dot org
@ 2008-05-03 20:12 ` jaydub66 at gmail dot com
  2008-05-03 20:45 ` jaydub66 at gmail dot com
  2008-05-04  0:29 ` jvdelisle at gcc dot gnu dot org
  3 siblings, 0 replies; 5+ messages in thread
From: jaydub66 at gmail dot com @ 2008-05-03 20:12 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from jaydub66 at gmail dot com  2008-05-03 20:11 -------
Confirmed. The ICEs you get are really due to my rev. 134867, which actually
also triggered some testsuite failures (use_only_1.f90 and g77/970915-0.f). I
have no idea why I didn't notice it (sorry!).

This can easily be fixed by the following small patch:

Index: gcc/fortran/misc.c
===================================================================
--- gcc/fortran/misc.c  (revision 134867)
+++ gcc/fortran/misc.c  (working copy)
@@ -77,6 +77,7 @@ gfc_clear_ts (gfc_typespec *ts)
   ts->derived = NULL;
   ts->kind = 0;
   ts->cl = NULL;
+  ts->interface = NULL;
   /* flag that says if the type is C interoperable */
   ts->is_c_interop = 0;
   /* says what f90 type the C kind interops with */


-- 


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


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

* [Bug fortran/36114] [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867
  2008-05-02 22:30 [Bug fortran/36114] New: [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867 dominiq at lps dot ens dot fr
  2008-05-03  9:12 ` [Bug fortran/36114] " rguenth at gcc dot gnu dot org
  2008-05-03 20:12 ` jaydub66 at gmail dot com
@ 2008-05-03 20:45 ` jaydub66 at gmail dot com
  2008-05-04  0:29 ` jvdelisle at gcc dot gnu dot org
  3 siblings, 0 replies; 5+ messages in thread
From: jaydub66 at gmail dot com @ 2008-05-03 20:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from jaydub66 at gmail dot com  2008-05-03 20:44 -------
Fixed with rev. 134918.


-- 


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


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

* [Bug fortran/36114] [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867
  2008-05-02 22:30 [Bug fortran/36114] New: [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867 dominiq at lps dot ens dot fr
                   ` (2 preceding siblings ...)
  2008-05-03 20:45 ` jaydub66 at gmail dot com
@ 2008-05-04  0:29 ` jvdelisle at gcc dot gnu dot org
  3 siblings, 0 replies; 5+ messages in thread
From: jvdelisle at gcc dot gnu dot org @ 2008-05-04  0:29 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from jvdelisle at gcc dot gnu dot org  2008-05-04 00:29 -------
Fixed by r 134918. Closing


-- 

jvdelisle at gcc dot gnu dot org changed:

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


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


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

end of thread, other threads:[~2008-05-04  0:29 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2008-05-02 22:30 [Bug fortran/36114] New: [4.4 Regression] "f951: internal compiler error: Bus error" due to revision 134867 dominiq at lps dot ens dot fr
2008-05-03  9:12 ` [Bug fortran/36114] " rguenth at gcc dot gnu dot org
2008-05-03 20:12 ` jaydub66 at gmail dot com
2008-05-03 20:45 ` jaydub66 at gmail dot com
2008-05-04  0:29 ` jvdelisle at gcc dot gnu dot 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).