Bug 50960

Summary: [OOP] vtables not marked as constant
Product: gcc Reporter: Tobias Burnus <burnus>
Component: fortranAssignee: janus
Status: RESOLVED FIXED    
Severity: normal CC: janus
Priority: P3 Keywords: missed-optimization
Version: 4.7.0   
Target Milestone: 4.7.0   
Host: Target:
Build: Known to work:
Known to fail: Last reconfirmed: 2011-11-02 00:00:00
Bug Depends on:    
Bug Blocks: 49993    

Description Tobias Burnus 2011-11-02 10:42:47 UTC
< richi> and it seems the vtables are not initialized in a way the
         optimizers could use them
< richi> they are not constant
< richi> your testcase should be trivially de-virtualizable by early FRE

For the test case, see PR 50959 comment 0
Comment 1 janus 2011-11-02 11:57:44 UTC
(In reply to comment #0)
> < richi> and it seems the vtables are not initialized in a way the
>          optimizers could use them
> < richi> they are not constant

Right. I had thought of making them PARAMETERS earlier (to use Fortran terminology). But in the early implementation this was not possible, since the PPC members of the vtabs were not initialized statically. Now they are, so this should work (in principle). I'll try if the following patch survives regtesting:

Index: gcc/fortran/class.c
===================================================================
--- gcc/fortran/class.c (revision 180713)
+++ gcc/fortran/class.c (working copy)
@@ -424,7 +424,7 @@ gfc_find_derived_vtab (gfc_symbol *derived)
        {
          gfc_get_symbol (name, ns, &vtab);
          vtab->ts.type = BT_DERIVED;
-         if (gfc_add_flavor (&vtab->attr, FL_VARIABLE, NULL,
+         if (gfc_add_flavor (&vtab->attr, FL_PARAMETER, NULL,
                              &gfc_current_locus) == FAILURE)
            goto cleanup;
          vtab->attr.target = 1;
Comment 2 Richard Biener 2011-11-02 14:32:13 UTC
Does not help.  The vtable objects are still not in .rodata:

        .data
        .align 32
        .type   __m_MOD___vtab_m_T2, @object
        .size   __m_MOD___vtab_m_T2, 40
__m_MOD___vtab_m_T2:
        .long   69979408
        .long   0
        .quad   __m_MOD___vtab_m_T
        .quad   __m_MOD___def_init_m_T2
        .quad   __m_MOD___copy_m_T2
        .quad   __m_MOD_ext

nor are reads from them optimized (-fdump-tree-fre-details, t.f90.027t.fre1):


<bb 6>:
  D.1793_12 = &__vtab_m_T;
  D.1794_13 = D.1793_12->bar;
  D.1794_13 ();

should have been simplified to the constant __vtab_m_T.bar is initialized
from.
Comment 3 Richard Biener 2011-11-02 14:37:35 UTC
The vtable object looks like (with the patch):

 <var_decl 0x7ffff5a2c280 __vtab_m_T
    type <record_type 0x7ffff5b37dc8 __vtype_m_T BLK
        size <integer_cst 0x7ffff5b12980 constant 320>
        unit size <integer_cst 0x7ffff5b129a0 constant 40>
        align 64 symtab 0 alias set -1 canonical type 0x7ffff5b37dc8
        fields <field_decl 0x7ffff5b31428 _hash type <integer_type 0x7ffff5a315e8 integer(kind=4)>
            SI file t.f90 line 18 col 0
            size <integer_cst 0x7ffff5a34240 constant 32>
            unit size <integer_cst 0x7ffff5a34260 constant 4>
            align 32 offset_align 128
            offset <integer_cst 0x7ffff5a20f00 constant 0>
            bit offset <integer_cst 0x7ffff5a20f60 constant 0> context <record_type 0x7ffff5b37dc8 __vtype_m_T> chain <field_decl 0x7ffff5b314c0 _size>> context <namespace_decl 0x7ffff5a4b7e8 m>
        pointer_to_this <pointer_type 0x7ffff5b37f18> chain <type_decl 0x7ffff5a4bcf0 D.1735>>
    addressable used public static BLK file t.f90 line 18 col 0 size <integer_cst 0x7ffff5b12980 320> unit size <integer_cst 0x7ffff5b129a0 40>
    align 256 context <namespace_decl 0x7ffff5a4b7e8 m> initial <constructor 0x7ffff5b1de70> chain <function_decl 0x7ffff5b38600 base>>

it is not TREE_READONLY.  The constructor looks ok:

{._hash=6736034, ._size=0, ._extends=0B, ._def_init=&__def_init_m_T, ._copy=__copy_m_T, .bar=base}

Instead of a VAR_DECL it could maybe also be a CONST_DECL(?).  But first
try setting TREE_READONLY on it.
Comment 4 Richard Biener 2011-11-02 14:40:09 UTC
Doing that in gdb yields to

<bb 6>:
  D.1793_12 = &__vtab_m_T;
  D.1794_13 = base;
  base ();

in the fre1 dump.
Comment 5 Tobias Burnus 2011-11-02 14:57:34 UTC
(In reply to comment #1)
> -         if (gfc_add_flavor (&vtab->attr, FL_VARIABLE, NULL,
> +         if (gfc_add_flavor (&vtab->attr, FL_PARAMETER, NULL,

(In reply to comment #3)
> it is not TREE_READONLY.

I wonder whether there is a general missed-optimization issue for FL_PARAMETER (for the case they are stored as actual data and not just as drop-in number). One might need some special handling, but I also do not see "para" ("__m_MOD_para:") marked as .rodata for

module m
  integer, parameter :: PARA(*) = [1,2,3,4,5,6,7,8,9,10]
end module m

use m
print *, para
end
Comment 6 janus 2011-11-02 15:08:28 UTC
(In reply to comment #1)
> I'll try if the following patch survives regtesting

It fails at least on:

FAIL: gfortran.dg/dynamic_dispatch_4.f03  -O0  (test for excess errors)
FAIL: gfortran.dg/dynamic_dispatch_5.f03  -O0  (test for excess errors)



> gfortran-4.7 dynamic_dispatch_4.f03 
dynamic_dispatch_4.f03:79.6:

  use s_bar_mod
      1
Error: Interface mismatch for procedure-pointer component 'getit' in structure constructor at (1): Type/rank mismatch in argument 'a'



> gfortran-4.7 dynamic_dispatch_5.f03 
dynamic_dispatch_5.f03:176.8:

    use s_mat_mod
        1
Error: Interface mismatch for procedure-pointer component 's_scals' in structure constructor at (1): Type/rank mismatch in argument 'a'
Comment 7 Richard Biener 2011-11-02 15:16:08 UTC
(In reply to comment #5)
> (In reply to comment #1)
> > -         if (gfc_add_flavor (&vtab->attr, FL_VARIABLE, NULL,
> > +         if (gfc_add_flavor (&vtab->attr, FL_PARAMETER, NULL,
> 
> (In reply to comment #3)
> > it is not TREE_READONLY.
> 
> I wonder whether there is a general missed-optimization issue for FL_PARAMETER
> (for the case they are stored as actual data and not just as drop-in number).
> One might need some special handling, but I also do not see "para"
> ("__m_MOD_para:") marked as .rodata for
> 
> module m
>   integer, parameter :: PARA(*) = [1,2,3,4,5,6,7,8,9,10]
> end module m
> 
> use m
> print *, para
> end

Definitely a missed optimization.  Optimizers will not be able to
propagate constants from that initializer.
Comment 8 janus 2011-11-02 16:44:56 UTC
(In reply to comment #6)
> It fails at least on:
> 
> FAIL: gfortran.dg/dynamic_dispatch_4.f03  -O0  (test for excess errors)

Here is a reduced test case:


module foo_mod
  type foo
  contains
    procedure, pass(a) :: getit
  end type
  private :: getit
contains
  integer function getit(a)
    class(foo) :: a
  end function
end module

module bar_mod 
  use foo_mod
  type :: bar
  end type
contains
  integer function getit(b)
    class(bar) :: b
  end function
end module

  use bar_mod
end



  use bar_mod
      1
Error: Interface mismatch for procedure-pointer component 'getit' in structure constructor at (1): Type/rank mismatch in argument 'a'


Apparently the error is due to two routines having the same names. When resolving the vtab of foo in the main program, the wrong one is used (since the other is not accessible). However, I don't quite see yet how that is connected to the FL_PARAMETER change.
Comment 9 janus 2011-11-02 18:49:35 UTC
(In reply to comment #6)
> It fails at least on:
> 
> FAIL: gfortran.dg/dynamic_dispatch_4.f03  -O0  (test for excess errors)
> FAIL: gfortran.dg/dynamic_dispatch_5.f03  -O0  (test for excess errors)


Those can be fixed by:

Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 180780)
+++ gcc/fortran/resolve.c	(working copy)
@@ -9503,7 +9503,7 @@ resolve_values (gfc_symbol *sym)
 {
   gfc_try t;
 
-  if (sym->value == NULL)
+  if (sym->value == NULL || sym->attr.use_assoc)
     return;
 
   if (sym->value->expr_type == EXPR_STRUCTURE)


Use-associated symbols should have been resolved before, so I guess we don't need to do it again? (At least this produces no further regressions.)


Apart from the two failures above, the patch in comment 1 also fails on:

FAIL: gfortran.dg/class_15.f03  -O  (internal compiler error)
FAIL: gfortran.dg/extends_type_of_1.f03  -O0  (internal compiler error)
FAIL: gfortran.dg/extends_type_of_3.f90  -O  (internal compiler error)

Those are not cured by the patchlet above.
Comment 10 janus 2011-11-02 20:11:01 UTC
(In reply to comment #9)
> Apart from the two failures above, the patch in comment 1 also fails on:
> 
> FAIL: gfortran.dg/class_15.f03  -O  (internal compiler error)

The reason for this seems to be some module loading problem: The vtype of 't2' is loaded from the module alright, while the vtab is not. As a consequence, sym->value is not set correctly (in 'gfc_find_derived_vtab'). I'm currently not sure how to fix the underlying problem, but the resulting segfault can be fixed by:

Index: resolve.c
===================================================================
--- resolve.c   (revision 180780)
+++ resolve.c   (working copy)
@@ -11971,7 +11971,7 @@ resolve_fl_parameter (gfc_symbol *sym)
   /* Make sure the types of derived parameters are consistent.  This
      type checking is deferred until resolution because the type may
      refer to a derived type from the host.  */
-  if (sym->ts.type == BT_DERIVED
+  if (sym->ts.type == BT_DERIVED && sym->value
       && !gfc_compare_types (&sym->ts, &sym->value->ts))
     {
       gfc_error ("Incompatible derived type in PARAMETER at %L",
Comment 11 janus 2011-11-02 21:17:11 UTC
(In reply to comment #9)
> FAIL: gfortran.dg/extends_type_of_1.f03  -O0  (internal compiler error)
> FAIL: gfortran.dg/extends_type_of_3.f90  -O  (internal compiler error)

These two fail with:

internal compiler error: in fold_convert_loc, at fold-const.c:1894

Not quite sure what goes wrong there. Some typing problem?


Reduced test case:

 type :: t1
 end type

 type, extends(t1) :: t2
 end type

 class(t1), pointer :: c1
 type(t2) :: y

 if (.not. extends_type_of (y, c1)) call abort()

end
Comment 12 janus 2011-11-03 12:06:48 UTC
In summary, the combined patches of comment 1, comment 9 and comment 10:


Index: gcc/fortran/class.c
===================================================================
--- gcc/fortran/class.c	(revision 180820)
+++ gcc/fortran/class.c	(working copy)
@@ -424,7 +424,7 @@ gfc_find_derived_vtab (gfc_symbol *derived)
 	{
 	  gfc_get_symbol (name, ns, &vtab);
 	  vtab->ts.type = BT_DERIVED;
-	  if (gfc_add_flavor (&vtab->attr, FL_VARIABLE, NULL,
+	  if (gfc_add_flavor (&vtab->attr, FL_PARAMETER, NULL,
 	                      &gfc_current_locus) == FAILURE)
 	    goto cleanup;
 	  vtab->attr.target = 1;
Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 180820)
+++ gcc/fortran/resolve.c	(working copy)
@@ -9503,7 +9503,7 @@ resolve_values (gfc_symbol *sym)
 {
   gfc_try t;
 
-  if (sym->value == NULL)
+  if (sym->value == NULL || sym->attr.use_assoc)
     return;
 
   if (sym->value->expr_type == EXPR_STRUCTURE)
@@ -11971,7 +11971,7 @@ resolve_fl_parameter (gfc_symbol *sym)
   /* Make sure the types of derived parameters are consistent.  This
      type checking is deferred until resolution because the type may
      refer to a derived type from the host.  */
-  if (sym->ts.type == BT_DERIVED
+  if (sym->ts.type == BT_DERIVED && sym->value
       && !gfc_compare_types (&sym->ts, &sym->value->ts))
     {
       gfc_error ("Incompatible derived type in PARAMETER at %L",



show two remaining testsuite failures:

FAIL: gfortran.dg/extends_type_of_1.f03  -O0  (internal compiler error)
FAIL: gfortran.dg/extends_type_of_3.f90  -O  (internal compiler error)

(cf. comment 11)
Comment 13 Tobias Burnus 2011-11-03 14:03:40 UTC
Patch for the issue of comment 5: Constants (PARAMETER) which are exists as global static variables were not marked as TREE_READONLY.

With the patch below (not regtested), the function call is optimized away in:

module m
  integer, parameter :: PARA(*) = [1,2,3,4,5,6,7,8,9,10]
end module m

subroutine test()
use m
integer :: i
i = 1
if (para(i) /= 1) call I_am_optimized_away()
end


--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -517,6 +517,9 @@ gfc_finish_var_decl (tree decl, gfc_symbol * sym)
   /* If it wasn't used we wouldn't be getting it.  */
   TREE_USED (decl) = 1;

+  if (sym->attr.flavor == FL_PARAMETER)
+    TREE_READONLY (decl) = 1;
+
   /* Chain this decl to the pending declarations.  Don't do pushdecl()
      because this would add them to the current scope rather than the
      function scope.  */
Comment 14 Richard Biener 2011-11-03 14:17:52 UTC
(In reply to comment #13)
> Patch for the issue of comment 5: Constants (PARAMETER) which are exists as
> global static variables were not marked as TREE_READONLY.
> 
> With the patch below (not regtested), the function call is optimized away in:
> 
> module m
>   integer, parameter :: PARA(*) = [1,2,3,4,5,6,7,8,9,10]
> end module m
> 
> subroutine test()
> use m
> integer :: i
> i = 1
> if (para(i) /= 1) call I_am_optimized_away()
> end
> 
> 
> --- a/gcc/fortran/trans-decl.c
> +++ b/gcc/fortran/trans-decl.c
> @@ -517,6 +517,9 @@ gfc_finish_var_decl (tree decl, gfc_symbol * sym)
>    /* If it wasn't used we wouldn't be getting it.  */
>    TREE_USED (decl) = 1;
> 
> +  if (sym->attr.flavor == FL_PARAMETER)
> +    TREE_READONLY (decl) = 1;
> +
>    /* Chain this decl to the pending declarations.  Don't do pushdecl()
>       because this would add them to the current scope rather than the
>       function scope.  */

Yes, that should work iff Fortran does not allow parameter initializers
that require runtime init (like / foo() /, thus a function call result).
Comment 15 Tobias Burnus 2011-11-03 14:23:59 UTC
(In reply to comment #14)
> Yes, that should work iff Fortran does not allow parameter initializers
> that require runtime init (like / foo() /, thus a function call result).

No, Fortran only has static initializers which are known at compile time. In principle, the parameters could also be inlined by FE compiler (as it is done for scalars), however, for large arrays, using a static global array seemed to be the better choice (which matches other compilers).

Hence, TREE_READONLY should be correct.
Comment 16 Richard Biener 2011-11-03 14:29:29 UTC
(In reply to comment #11)
> (In reply to comment #9)
> > FAIL: gfortran.dg/extends_type_of_1.f03  -O0  (internal compiler error)
> > FAIL: gfortran.dg/extends_type_of_3.f90  -O  (internal compiler error)
> 
> These two fail with:
> 
> internal compiler error: in fold_convert_loc, at fold-const.c:1894
> 
> Not quite sure what goes wrong there. Some typing problem?
> 
> 
> Reduced test case:
> 
>  type :: t1
>  end type
> 
>  type, extends(t1) :: t2
>  end type
> 
>  class(t1), pointer :: c1
>  type(t2) :: y
> 
>  if (.not. extends_type_of (y, c1)) call abort()
> 
> end

Looks like you are converting struct __vtype_MAIN___T1 to
struct __vtype_MAIN___T1 *.  Thus probably too many TREE_TYPE ()
wrappers somewhere or a forgotten address-taking.

Called from

4608            {
4609              /* Scalar pointers.  */
4610              se.want_pointer = 1;
4611              gfc_conv_expr (&se, expr);
4612              gfc_add_block_to_block (&block, &se.pre);
4613              gfc_add_modify (&block, dest,
4614                                   fold_convert (TREE_TYPE (dest), se.expr))

where se.want_pointer (whatever it means) is not honored and se.expr
is a variable of type struct __vtype_MAIN___T1.
Comment 17 Richard Biener 2011-11-03 14:34:02 UTC
(In reply to comment #16)
> (In reply to comment #11)
> > (In reply to comment #9)
> > > FAIL: gfortran.dg/extends_type_of_1.f03  -O0  (internal compiler error)
> > > FAIL: gfortran.dg/extends_type_of_3.f90  -O  (internal compiler error)
> > 
> > These two fail with:
> > 
> > internal compiler error: in fold_convert_loc, at fold-const.c:1894
> > 
> > Not quite sure what goes wrong there. Some typing problem?
> > 
> > 
> > Reduced test case:
> > 
> >  type :: t1
> >  end type
> > 
> >  type, extends(t1) :: t2
> >  end type
> > 
> >  class(t1), pointer :: c1
> >  type(t2) :: y
> > 
> >  if (.not. extends_type_of (y, c1)) call abort()
> > 
> > end
> 
> Looks like you are converting struct __vtype_MAIN___T1 to
> struct __vtype_MAIN___T1 *.  Thus probably too many TREE_TYPE ()
> wrappers somewhere or a forgotten address-taking.
> 
> Called from
> 
> 4608            {
> 4609              /* Scalar pointers.  */
> 4610              se.want_pointer = 1;
> 4611              gfc_conv_expr (&se, expr);
> 4612              gfc_add_block_to_block (&block, &se.pre);
> 4613              gfc_add_modify (&block, dest,
> 4614                                   fold_convert (TREE_TYPE (dest),
> se.expr))
> 
> where se.want_pointer (whatever it means) is not honored and se.expr
> is a variable of type struct __vtype_MAIN___T1.

Missing handling of se.want_pointer at least here:

void
gfc_conv_structure (gfc_se * se, gfc_expr * expr, int init)
{
...
  if (!init)
    {
      /* Create a temporary variable and fill it in.  */
      se->expr = gfc_create_var (type, expr->ts.u.derived->name);
      tmp = gfc_trans_structure_assign (se->expr, expr);
      gfc_add_expr_to_block (&se->pre, tmp);
      return;

but what's the desire of the caller?  Is it to get &expr?  Something
seems to be seriously wrong.
Comment 18 Tobias Burnus 2011-11-03 22:32:42 UTC
Author: burnus
Date: Thu Nov  3 22:32:37 2011
New Revision: 180878

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=180878
Log:
2011-11-03  Tobias Burnus  <burnus@net-b.de>

        PR fortran/50960
        * trans-decl.c (gfc_finish_var_decl): Mark PARAMETER as
        * TREE_READONLY.

2011-11-03  Tobias Burnus  <burnus@net-b.de>

        PR fortran/50960
        * gfortran.dg/module_parameter_array_refs_2.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/module_parameter_array_refs_2.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-decl.c
    trunk/gcc/testsuite/ChangeLog
Comment 19 Tobias Burnus 2011-11-07 07:35:24 UTC
See also PR 50640 comment 16 and the patch in attachment 25730 [details]
Comment 20 janus 2011-11-07 22:57:46 UTC
(In reply to comment #17)
> Missing handling of se.want_pointer at least here:
> 
> void
> gfc_conv_structure (gfc_se * se, gfc_expr * expr, int init)
> {
> ...
>   if (!init)
>     {
>       /* Create a temporary variable and fill it in.  */
>       se->expr = gfc_create_var (type, expr->ts.u.derived->name);
>       tmp = gfc_trans_structure_assign (se->expr, expr);
>       gfc_add_expr_to_block (&se->pre, tmp);
>       return;
> 
> but what's the desire of the caller?  Is it to get &expr?  Something
> seems to be seriously wrong.

Indeed. The funny thing is that we have to deal with an EXPR_STRUCTURE at all, not with an EXPR_VARIABLE. This is because the __vtab_... variable is replaced with its value (which happens in simplify_parameter_variable). Of course this should not happen, and the trouble starts when we try to take the address of the EXPR_STRUCTURE ...

Here is a patch which prevents simplifying a parameter variable which is a vtab:

Index: gcc/fortran/expr.c
===================================================================
--- gcc/fortran/expr.c	(revision 181106)
+++ gcc/fortran/expr.c	(working copy)
@@ -1883,7 +1883,8 @@ gfc_simplify_expr (gfc_expr *p, int type)
 	 initialization expression, or we want a subsection.  */
       if (p->symtree->n.sym->attr.flavor == FL_PARAMETER
 	  && (gfc_init_expr_flag || p->ref
-	      || p->symtree->n.sym->value->expr_type != EXPR_ARRAY))
+	      || p->symtree->n.sym->value->expr_type != EXPR_ARRAY)
+	  && !p->symtree->n.sym->attr.vtab)
 	{
 	  if (simplify_parameter_variable (p, type) == FAILURE)
 	    return FAILURE;


With this, the extends_type_of* tests work as expected. So: No more regressions!
Comment 21 janus 2011-11-09 09:45:38 UTC
Author: janus
Date: Wed Nov  9 09:45:36 2011
New Revision: 181199

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=181199
Log:
2011-11-09  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/50960
	* class.c (gfc_find_derived_vtab): Make the vtab symbols FL_PARAMETER.
	* expr.c (gfc_simplify_expr): Prevent vtabs from being replaced with
	their value.
	* resolve.c (resolve_values): Use-associated symbols do not need to
	be resolved again.
	(resolve_fl_parameter): Make sure the symbol has a value.

Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/class.c
    trunk/gcc/fortran/expr.c
    trunk/gcc/fortran/resolve.c
Comment 22 janus 2011-11-09 15:56:57 UTC
Author: janus
Date: Wed Nov  9 15:56:53 2011
New Revision: 181208

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=181208
Log:
2011-11-09  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/50960
	* gfortran.dg/typebound_call_22.f03: New test case.

Added:
    trunk/gcc/testsuite/gfortran.dg/typebound_call_22.f03
Modified:
    trunk/gcc/testsuite/ChangeLog
Comment 23 janus 2011-11-09 15:59:26 UTC
Ok, after the all the issues have been fixed and we have a test case to verify that 'devirtualization' actually works, I think it's about time to close this one.