public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
@ 2013-01-10 15:37 burnus at gcc dot gnu.org
  2013-01-10 16:01 ` [Bug fortran/55935] " dominiq at lps dot ens.fr
                   ` (16 more replies)
  0 siblings, 17 replies; 18+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-01-10 15:37 UTC (permalink / raw)
  To: gcc-bugs


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

             Bug #: 55935
           Summary: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs
                    with bogus BLOCK
    Classification: Unclassified
           Product: gcc
           Version: 4.8.0
            Status: UNCONFIRMED
          Keywords: ice-on-valid-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: burnus@gcc.gnu.org
                CC: janus@gcc.gnu.org, pault@gcc.gnu.org


I assume that that relates to the __copy function.

>From PR 55792 comment 29:
-------------------------

The Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs which have a location
with bogus BLOCK.

> Also verify expressions.  Bootstrapped ok, target libs building now, testing
> pending.

FAIL: gfortran.dg/class_array_15.f03  -O0  (internal compiler error)
FAIL: gfortran.dg/typebound_operator_13.f03  -O0  (internal compiler error)
FAIL: gfortran.dg/typebound_operator_7.f03  -O0  (internal compiler error)
FAIL: gfortran.dg/typebound_operator_8.f03  -O0  (internal compiler error)


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
@ 2013-01-10 16:01 ` dominiq at lps dot ens.fr
  2013-01-10 16:25 ` dominiq at lps dot ens.fr
                   ` (15 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-10 16:01 UTC (permalink / raw)
  To: gcc-bugs


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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2013-01-10
     Ever Confirmed|0                           |1

--- Comment #1 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-10 16:00:46 UTC ---
> I assume that that relates to the __copy function.

It looks likely: with the patch at
http://gcc.gnu.org/ml/gcc-patches/2013-01/msg00547.html, I get

[macbook] f90/bug% gfc
/opt/gcc/work/gcc/testsuite/gfortran.dg/class_array_15.f03
/opt/gcc/work/gcc/testsuite/gfortran.dg/class_array_15.f03: In function
'pr54992':
/opt/gcc/work/gcc/testsuite/gfortran.dg/class_array_15.f03:97:0: error:
location references block not in block tree
 subroutine pr54992  ! This test remains as the original.
 ^
__copy_g_nodes_Ncbhstd
_22 = __copy_g_nodes_Ncbhstd;

/opt/gcc/work/gcc/testsuite/gfortran.dg/class_array_15.f03:97:0: internal
compiler error: verify_gimple failed

and so on for the other failing tests.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
  2013-01-10 16:01 ` [Bug fortran/55935] " dominiq at lps dot ens.fr
@ 2013-01-10 16:25 ` dominiq at lps dot ens.fr
  2013-01-10 16:29 ` jakub at gcc dot gnu.org
                   ` (14 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-10 16:25 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #2 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-10 16:25:05 UTC ---
For the test gfortran.dg/class_array_15.f03, the ICE is triggered by the
statement:

allocate(b%cBh(1),source=defaultBhC)

(note that the test compiles with  -fno-whole-file;-).


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
  2013-01-10 16:01 ` [Bug fortran/55935] " dominiq at lps dot ens.fr
  2013-01-10 16:25 ` dominiq at lps dot ens.fr
@ 2013-01-10 16:29 ` jakub at gcc dot gnu.org
  2013-01-10 17:35 ` dominiq at lps dot ens.fr
                   ` (13 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-01-10 16:29 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #3 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-01-10 16:29:17 UTC ---
Supposedly ADDR_EXPR is shared between several functions or something similar.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2013-01-10 16:29 ` jakub at gcc dot gnu.org
@ 2013-01-10 17:35 ` dominiq at lps dot ens.fr
  2013-01-10 22:35 ` dominiq at lps dot ens.fr
                   ` (12 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-10 17:35 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #4 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-10 17:35:13 UTC ---
> (note that the test compiles with  -fno-whole-file;-).

To be honest, this is not true for the other failing tests. Reduced
typebound_operator_8.f03

! { dg-do compile }
! PR48946 - complex expressions involving typebound operators of derived types.
!
module field_module
  implicit none
  type ,abstract :: field
  contains
    procedure(field_op_real) ,deferred :: multiply_real
    procedure(field_plus_field) ,deferred :: plus
    generic :: operator(*) => multiply_real
    generic :: operator(+) => plus
  end type
  abstract interface
    function field_plus_field(lhs,rhs)
      import :: field
      class(field) ,intent(in)  :: lhs
      class(field) ,intent(in)  :: rhs
      class(field) ,allocatable :: field_plus_field
    end function
  end interface
  abstract interface
    function field_op_real(lhs,rhs)
      import :: field
      class(field) ,intent(in)  :: lhs
      real ,intent(in) :: rhs
      class(field) ,allocatable :: field_op_real
    end function
  end interface
end module

module i_field_module
  use field_module
  implicit none
  type, extends (field)  :: i_field
    integer :: i
  contains
    procedure :: multiply_real => i_multiply_real
    procedure :: plus => i_plus_i
  end type
contains
  function i_plus_i(lhs,rhs)
    class(i_field) ,intent(in)  :: lhs
    class(field) ,intent(in)  :: rhs
    class(field) ,allocatable :: i_plus_i
    integer :: m = 0
    select type (lhs)
      type is (i_field); m = lhs%i
    end select
    select type (rhs)
      type is (i_field); m = rhs%i + m
    end select
    allocate (i_plus_i, source = i_field (m))
  end function
  function i_multiply_real(lhs,rhs)
    class(i_field) ,intent(in)  :: lhs
    real ,intent(in) :: rhs
    class(field) ,allocatable :: i_multiply_real
    integer :: m = 0
    select type (lhs)
      type is (i_field); m = lhs%i * int (rhs)
    end select
    allocate (i_multiply_real, source = i_field (m))
  end function
end module

This test compiles if I comment one of the ALLOCATE.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2013-01-10 17:35 ` dominiq at lps dot ens.fr
@ 2013-01-10 22:35 ` dominiq at lps dot ens.fr
  2013-01-10 23:11 ` dominiq at lps dot ens.fr
                   ` (11 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-10 22:35 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-10 22:35:06 UTC ---
Shorter test case for gfortran.dg/typebound_operator_*:

module i_field_module
  implicit none
  type :: i_field
    integer :: i
  end type
contains
  function i_plus_i(lhs)
    class(i_field) ,intent(in)  :: lhs
    class(i_field) ,allocatable :: i_plus_i
    allocate (i_plus_i, source = i_field (0))
  end function
  function i_multiply_real(lhs)
    class(i_field) ,intent(in)  :: lhs
    class(i_field) ,allocatable :: i_multiply_real
    allocate (i_multiply_real, source = i_field (0))
  end function
end module

Note that if the 'class's are replaced with 'type's, the program compiles.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2013-01-10 22:35 ` dominiq at lps dot ens.fr
@ 2013-01-10 23:11 ` dominiq at lps dot ens.fr
  2013-01-11  9:19 ` jakub at gcc dot gnu.org
                   ` (10 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-10 23:11 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-10 23:10:39 UTC ---
> Note that if the 'class's are replaced with 'type's, the program compiles.

The assert also triggers if

    class(i_field) ,intent(in)  :: lhs

is replaced with

    type(i_field) ,intent(in)  :: lhs


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2013-01-10 23:11 ` dominiq at lps dot ens.fr
@ 2013-01-11  9:19 ` jakub at gcc dot gnu.org
  2013-01-11 10:03 ` jakub at gcc dot gnu.org
                   ` (9 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-01-11  9:19 UTC (permalink / raw)
  To: gcc-bugs


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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |ASSIGNED
         AssignedTo|unassigned at gcc dot       |jakub at gcc dot gnu.org
                   |gnu.org                     |

--- Comment #7 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-01-11 09:18:41 UTC ---
Created attachment 29142
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=29142
gcc48-pr55935.patch

Untested fix.  Although the FE perhaps could unshare_expr_without_location so
that ADDR_EXPRs in the ctor don't have location, IMHO gimple-fold.c still has
to at least unshare_expr those expressions it copies from the constructors,
otherwise we'll end up with invalid sharing of ADDR_EXPRs etc. between
different functions (or within the same function).

This can be reproduced even with C:
void foo (void);
struct S { int i; void (*fn) (); };
const struct S s = { 5, foo };
void *fn1 (int x) { if (x < 0) return s.fn; if (x) return 0; return s.fn; }
void *fn2 (int x) { if (x < 0) return s.fn; if (x) return 0; return s.fn; }
void *fn3 (void) { return s.fn; }
void *fn4 (void) { return s.fn; }
at -O2, in *.copyrename1 pass all 6 ADDR_EXPRs in the IL are still shared.
ccp1 for whatever reason unshares them all (surprisingly).


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2013-01-11  9:19 ` jakub at gcc dot gnu.org
@ 2013-01-11 10:03 ` jakub at gcc dot gnu.org
  2013-01-11 13:36 ` dominiq at lps dot ens.fr
                   ` (8 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-01-11 10:03 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-01-11 10:03:09 UTC ---
Created attachment 29143
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=29143
gcc48-pr55935.patch

Or alternative patch that ensures in the FE there are no locations in the ctor
expressions, and just unshare_expr in the middle-end.  But I tend to prefer the
other patch.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2013-01-11 10:03 ` jakub at gcc dot gnu.org
@ 2013-01-11 13:36 ` dominiq at lps dot ens.fr
  2013-01-11 13:44 ` rguenth at gcc dot gnu.org
                   ` (7 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: dominiq at lps dot ens.fr @ 2013-01-11 13:36 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2013-01-11 13:35:30 UTC ---
Apparently Ada does not like the patch at

http://gcc.gnu.org/bugzilla/attachment.cgi?id=29142

When applied on top of r195103 bootstrap (last successful bootstrap was
r195098)  fails with

/opt/gcc/build_w/./prev-gcc/xgcc -B/opt/gcc/build_w/./prev-gcc/
-B/opt/gcc/gcc4.8w/x86_64-apple-darwin10.8.0/bin/
-B/opt/gcc/gcc4.8w/x86_64-apple-darwin10.8.0/bin/
-B/opt/gcc/gcc4.8w/x86_64-apple-darwin10.8.0/lib/ -isystem
/opt/gcc/gcc4.8w/x86_64-apple-darwin10.8.0/include -isystem
/opt/gcc/gcc4.8w/x86_64-apple-darwin10.8.0/sys-include    -c -g -O2
-mdynamic-no-pic -gtoggle  -gnatpg -gnata -W -Wall -nostdinc -I- -I. -Iada
-I../../work/gcc/ada -I../../work/gcc/ada/gcc-interface
../../work/gcc/ada/osint-c.adb -o ada/osint-c.o
/var/tmp//ccKGjE41.s:619:FATAL:Symbol LC0 already defined.

When I'll have finished a bootstrap without the patch, I'll try the patch for
gcc/fortran/trans-expr.c.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2013-01-11 13:36 ` dominiq at lps dot ens.fr
@ 2013-01-11 13:44 ` rguenth at gcc dot gnu.org
  2013-01-11 14:06 ` rguenth at gcc dot gnu.org
                   ` (6 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: rguenth at gcc dot gnu.org @ 2013-01-11 13:44 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #10 from Richard Biener <rguenth at gcc dot gnu.org> 2013-01-11 13:43:50 UTC ---
(In reply to comment #7)
> Created attachment 29142 [details]
> gcc48-pr55935.patch
> 
> Untested fix.  Although the FE perhaps could unshare_expr_without_location so
> that ADDR_EXPRs in the ctor don't have location, IMHO gimple-fold.c still has
> to at least unshare_expr those expressions it copies from the constructors,
> otherwise we'll end up with invalid sharing of ADDR_EXPRs etc. between
> different functions (or within the same function).
> 
> This can be reproduced even with C:
> void foo (void);
> struct S { int i; void (*fn) (); };
> const struct S s = { 5, foo };
> void *fn1 (int x) { if (x < 0) return s.fn; if (x) return 0; return s.fn; }
> void *fn2 (int x) { if (x < 0) return s.fn; if (x) return 0; return s.fn; }
> void *fn3 (void) { return s.fn; }
> void *fn4 (void) { return s.fn; }
> at -O2, in *.copyrename1 pass all 6 ADDR_EXPRs in the IL are still shared.
> ccp1 for whatever reason unshares them all (surprisingly).

We allow those to pass verification in verify_node_sharing because:

/* Return true when the T can be shared.  */

bool
tree_node_can_be_shared (tree t)
{
  if (IS_TYPE_OR_DECL_P (t)
      || TREE_CODE (t) == SSA_NAME
      || is_gimple_min_invariant (t)
      || t == error_mark_node
      || TREE_CODE (t) == IDENTIFIER_NODE)
    return true;

is_gimple_min_invariant is bogus here IMHO.  But I guess "fixing" that
might have quite some fallout ...

Btw, get_symbol_constant_value also unshares the result from
canonicalize_constructor_val (if it's is_gimple_min_invariant).

I suppose we should try fixing tree_node_can_be_shared ...


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2013-01-11 13:44 ` rguenth at gcc dot gnu.org
@ 2013-01-11 14:06 ` rguenth at gcc dot gnu.org
  2013-01-11 14:31 ` rguenth at gcc dot gnu.org
                   ` (5 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: rguenth at gcc dot gnu.org @ 2013-01-11 14:06 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #11 from Richard Biener <rguenth at gcc dot gnu.org> 2013-01-11 14:05:14 UTC ---
Created attachment 29145
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=29145
alternative canonicalize_constructor_val fix

Should be less expensive.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2013-01-11 14:06 ` rguenth at gcc dot gnu.org
@ 2013-01-11 14:31 ` rguenth at gcc dot gnu.org
  2013-01-11 14:41 ` jakub at gcc dot gnu.org
                   ` (4 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: rguenth at gcc dot gnu.org @ 2013-01-11 14:31 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #12 from Richard Biener <rguenth at gcc dot gnu.org> 2013-01-11 14:30:29 UTC ---
Index: gcc/tree-cfgcleanup.c
===================================================================
--- gcc/tree-cfgcleanup.c       (revision 195103)
+++ gcc/tree-cfgcleanup.c       (working copy)
@@ -412,7 +412,8 @@ remove_forwarder_block (basic_block bb)
            {
              gimple phi = gsi_stmt (gsi);
              source_location l = gimple_phi_arg_location_from_edge (phi,
succ);
-             add_phi_arg (phi, gimple_phi_arg_def (phi, succ->dest_idx), s,
l);
+             tree def = gimple_phi_arg_def (phi, succ->dest_idx);
+             add_phi_arg (phi, unshare_expr (def), s, l);
            }
        }
     }

is the only other that triggers in tree-ssa.exp with

Index: gcc/tree-cfg.c
===================================================================
--- gcc/tree-cfg.c      (revision 195103)
+++ gcc/tree-cfg.c      (working copy)
@@ -4440,8 +4460,8 @@ bool
 tree_node_can_be_shared (tree t)
 {
   if (IS_TYPE_OR_DECL_P (t)
-      || is_gimple_min_invariant (t)
       || TREE_CODE (t) == SSA_NAME
+      || CONSTANT_CLASS_P (t)
       || t == error_mark_node
       || TREE_CODE (t) == IDENTIFIER_NODE)
     return true;

execute.exp has more issue it seems.


removal of the handled_component_p block from tree_node_can_be_shared
has bootstrapped all languages ok, testing is still in progress.


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (11 preceding siblings ...)
  2013-01-11 14:31 ` rguenth at gcc dot gnu.org
@ 2013-01-11 14:41 ` jakub at gcc dot gnu.org
  2013-01-11 14:54 ` rguenth at gcc dot gnu.org
                   ` (3 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-01-11 14:41 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #13 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-01-11 14:40:45 UTC ---
Created attachment 29148
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=29148
gimple-fold

Alternative to alternative canonicalize_constructor_val fix which I'm afraid
could sometimes unshare up to 3 times.

Or we could just tree orig_cval = cval = unshare_expr (cval); as the first
thing in the function (and drop the unshare_expr in fold_gimple_assign of
course).


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (12 preceding siblings ...)
  2013-01-11 14:41 ` jakub at gcc dot gnu.org
@ 2013-01-11 14:54 ` rguenth at gcc dot gnu.org
  2013-01-11 14:56 ` rguenth at gcc dot gnu.org
                   ` (2 subsequent siblings)
  16 siblings, 0 replies; 18+ messages in thread
From: rguenth at gcc dot gnu.org @ 2013-01-11 14:54 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #14 from Richard Biener <rguenth at gcc dot gnu.org> 2013-01-11 14:53:20 UTC ---
(In reply to comment #13)
> Created attachment 29148 [details]
> gimple-fold
> 
> Alternative to alternative canonicalize_constructor_val fix which I'm afraid
> could sometimes unshare up to 3 times.
> 
> Or we could just tree orig_cval = cval = unshare_expr (cval); as the first
> thing in the function (and drop the unshare_expr in fold_gimple_assign of
> course).

I think I prefer the latter.

Another one, hits gcc.c-torture/execute/20000910-1.c at -O3 -g

Index: tree-ssa.c
===================================================================
--- tree-ssa.c  (revision 195103)
+++ tree-ssa.c  (working copy)
@@ -427,7 +427,7 @@ insert_debug_temp_for_var_def (gimple_st
              && (!gimple_assign_single_p (def_stmt)
                  || is_gimple_min_invariant (value)))
          || is_gimple_reg (value))
-       value = unshare_expr (value);
+       ;
       else
        {
          gimple def_temp;
@@ -469,7 +469,7 @@ insert_debug_temp_for_var_def (gimple_st
               that was unshared when we found it had a single debug
               use, or a DEBUG_EXPR_DECL, that can be safely
               shared.  */
-           SET_USE (use_p, value);
+           SET_USE (use_p, unshare_expr (value));
          /* If we didn't replace uses with a debug decl fold the
             resulting expression.  Otherwise we end up with invalid IL.  */
          if (TREE_CODE (value) != DEBUG_EXPR_DECL)


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (13 preceding siblings ...)
  2013-01-11 14:54 ` rguenth at gcc dot gnu.org
@ 2013-01-11 14:56 ` rguenth at gcc dot gnu.org
  2013-01-13 12:34 ` jakub at gcc dot gnu.org
  2013-01-13 16:54 ` jakub at gcc dot gnu.org
  16 siblings, 0 replies; 18+ messages in thread
From: rguenth at gcc dot gnu.org @ 2013-01-11 14:56 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #15 from Richard Biener <rguenth at gcc dot gnu.org> 2013-01-11 14:55:55 UTC ---
Index: tree-ssa-pre.c
===================================================================
--- tree-ssa-pre.c      (revision 195103)
+++ tree-ssa-pre.c      (working copy)
@@ -3246,7 +3246,8 @@ insert_into_preds_of_block (basic_block
       gcc_assert (get_expr_type (ae) == type
                  || useless_type_conversion_p (type, get_expr_type (ae)));
       if (ae->kind == CONSTANT)
-       add_phi_arg (phi, PRE_EXPR_CONSTANT (ae), pred, UNKNOWN_LOCATION);
+       add_phi_arg (phi, unshare_expr (PRE_EXPR_CONSTANT (ae)),
+                    pred, UNKNOWN_LOCATION);
       else
        add_phi_arg (phi, PRE_EXPR_NAME (ae), pred, UNKNOWN_LOCATION);
     }


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (14 preceding siblings ...)
  2013-01-11 14:56 ` rguenth at gcc dot gnu.org
@ 2013-01-13 12:34 ` jakub at gcc dot gnu.org
  2013-01-13 16:54 ` jakub at gcc dot gnu.org
  16 siblings, 0 replies; 18+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-01-13 12:34 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #16 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-01-13 12:33:49 UTC ---
Author: jakub
Date: Sun Jan 13 12:33:43 2013
New Revision: 195136

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=195136
Log:
    PR fortran/55935
    * gimple-fold.c (get_symbol_constant_value): Call
    unshare_expr.
    (fold_gimple_assign): Don't call unshare_expr here.
    (fold_ctor_reference): Call unshare_expr.

    * trans-expr.c (gfc_conv_structure): Call
    unshare_expr_without_location on the ctor elements.

Modified:
    trunk/gcc/ChangeLog
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/gimple-fold.c


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

* [Bug fortran/55935] [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK
  2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
                   ` (15 preceding siblings ...)
  2013-01-13 12:34 ` jakub at gcc dot gnu.org
@ 2013-01-13 16:54 ` jakub at gcc dot gnu.org
  16 siblings, 0 replies; 18+ messages in thread
From: jakub at gcc dot gnu.org @ 2013-01-13 16:54 UTC (permalink / raw)
  To: gcc-bugs


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

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

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

--- Comment #17 from Jakub Jelinek <jakub at gcc dot gnu.org> 2013-01-13 16:54:28 UTC ---
Fixed.


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

end of thread, other threads:[~2013-01-13 16:54 UTC | newest]

Thread overview: 18+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2013-01-10 15:37 [Bug fortran/55935] New: [OOP] Fortran fronted has ADDR_EXPRs of FUNCTION_DECLs with bogus BLOCK burnus at gcc dot gnu.org
2013-01-10 16:01 ` [Bug fortran/55935] " dominiq at lps dot ens.fr
2013-01-10 16:25 ` dominiq at lps dot ens.fr
2013-01-10 16:29 ` jakub at gcc dot gnu.org
2013-01-10 17:35 ` dominiq at lps dot ens.fr
2013-01-10 22:35 ` dominiq at lps dot ens.fr
2013-01-10 23:11 ` dominiq at lps dot ens.fr
2013-01-11  9:19 ` jakub at gcc dot gnu.org
2013-01-11 10:03 ` jakub at gcc dot gnu.org
2013-01-11 13:36 ` dominiq at lps dot ens.fr
2013-01-11 13:44 ` rguenth at gcc dot gnu.org
2013-01-11 14:06 ` rguenth at gcc dot gnu.org
2013-01-11 14:31 ` rguenth at gcc dot gnu.org
2013-01-11 14:41 ` jakub at gcc dot gnu.org
2013-01-11 14:54 ` rguenth at gcc dot gnu.org
2013-01-11 14:56 ` rguenth at gcc dot gnu.org
2013-01-13 12:34 ` jakub at gcc dot gnu.org
2013-01-13 16:54 ` 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).