public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* Re: Fix PR45586 (type confusion ICEs), take 2
@ 2011-02-14 22:17 Dominique Dhumieres
  2011-02-15 17:19 ` Michael Matz
  0 siblings, 1 reply; 7+ messages in thread
From: Dominique Dhumieres @ 2011-02-14 22:17 UTC (permalink / raw)
  To: fortran; +Cc: gcc-patches, burnus, mikael.morin, matz

Michael,

With the patch take2, the test for pr47455 in comment #5
( http://gcc.gnu.org/bugzilla/attachment.cgi?id=23136 ) gives an ICE:

Program received signal EXC_BAD_ACCESS, Could not access memory.
Reason: KERN_INVALID_ADDRESS at address: 0x0000000000000000
0x00000001000cd940 in gfc_finish_var_decl (decl=0x141ddc280, sym=0x141c20440) at ../../work/gcc/fortran/trans-decl.c:566
566	      && INTEGER_CST_P (DECL_SIZE_UNIT (decl))
(gdb) bt
#0  0x00000001000cd940 in gfc_finish_var_decl (decl=0x141ddc280, sym=0x141c20440) at ../../work/gcc/fortran/trans-decl.c:566
#1  0x00000001000cc6d3 in gfc_get_symbol_decl (sym=0x141c20440) at ../../work/gcc/fortran/trans-decl.c:1288

This is not the case with the take 1.

Dominique

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

* Re: Fix PR45586 (type confusion ICEs), take 2
  2011-02-14 22:17 Fix PR45586 (type confusion ICEs), take 2 Dominique Dhumieres
@ 2011-02-15 17:19 ` Michael Matz
  2011-02-17 13:30   ` Fix PR45586 (type confusion ICEs), take 3 Michael Matz
  0 siblings, 1 reply; 7+ messages in thread
From: Michael Matz @ 2011-02-15 17:19 UTC (permalink / raw)
  To: Dominique Dhumieres; +Cc: fortran, gcc-patches, burnus, mikael.morin

Hi,

On Mon, 14 Feb 2011, Dominique Dhumieres wrote:

> Michael,
> 
> With the patch take2, the test for pr47455 in comment #5
> ( http://gcc.gnu.org/bugzilla/attachment.cgi?id=23136 ) gives an ICE:
> 
> Program received signal EXC_BAD_ACCESS, Could not access memory.
> Reason: KERN_INVALID_ADDRESS at address: 0x0000000000000000
> 0x00000001000cd940 in gfc_finish_var_decl (decl=0x141ddc280, sym=0x141c20440) at ../../work/gcc/fortran/trans-decl.c:566
> 566	      && INTEGER_CST_P (DECL_SIZE_UNIT (decl))
> (gdb) bt
> #0  0x00000001000cd940 in gfc_finish_var_decl (decl=0x141ddc280, sym=0x141c20440) at ../../work/gcc/fortran/trans-decl.c:566
> #1  0x00000001000cc6d3 in gfc_get_symbol_decl (sym=0x141c20440) at ../../work/gcc/fortran/trans-decl.c:1288
> 
> This is not the case with the take 1.

I see.  The underlying reason is that the type I construct a copy of isn't 
yet layed out.  I'll fix that.


Ciao,
Michael.

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

* Re: Fix PR45586 (type confusion ICEs), take 3
  2011-02-15 17:19 ` Michael Matz
@ 2011-02-17 13:30   ` Michael Matz
  2011-02-17 19:40     ` Mikael Morin
  0 siblings, 1 reply; 7+ messages in thread
From: Michael Matz @ 2011-02-17 13:30 UTC (permalink / raw)
  To: Dominique Dhumieres, mikael.morin; +Cc: fortran, gcc-patches, burnus

Hello,

On Tue, 15 Feb 2011, Michael Matz wrote:

> On Mon, 14 Feb 2011, Dominique Dhumieres wrote:
> 
> > Michael,
> > 
> > With the patch take2, the test for pr47455 in comment #5
> > ( http://gcc.gnu.org/bugzilla/attachment.cgi?id=23136 ) gives an ICE:
> 
> I see.  The underlying reason is that the type I construct a copy of 
> isn't yet layed out.  I'll fix that.

Was a bit more involved than I thought.  During construction of real class 
types (where members are function pointers, and those functions themself 
take a this argument of pointer to class) new fields are added to the 
record_type when we've already created the nonrestrict variant.  For that 
I've split out the field mirroring and use it in case we don't find the 
field we're searching for.  Additionally there was some problem with me 
using copy_node, I'm now using the more proper build_variant_type_copy.  
Otherwise patch is unchanged.

Regstrapped on x86_64-linux, no regressions.  I'm assuming that the 
testcase for pr47455 (typebound_proc_20.f90) goes into the tree when that 
bug is fixed for good, so I'm not adding it for this one.

Okay for trunk?


Ciao,
Michael.
-- 
fortran/
	PR fortran/45586
	* gfortran.h (struct gfc_component): Add norestrict_decl member.
	* trans.h (mirror_fields): Declare function.
	(struct lang_type): Add nonrestricted_type member.
	* trans-expr.c (gfc_conv_component_ref): Search fields with correct
	parent type.
	* trans-types.c (mirror_fields, gfc_nonrestricted_type): New.
	(gfc_sym_type): Use it.

testsuite/
	PR fortran/45586
	* gfortran.dg/lto/pr45586_0.f90: New test.

Index: trans-expr.c
===================================================================
--- trans-expr.c	(revision 170097)
+++ trans-expr.c	(working copy)
@@ -504,6 +504,38 @@ gfc_conv_component_ref (gfc_se * se, gfc
   field = c->backend_decl;
   gcc_assert (TREE_CODE (field) == FIELD_DECL);
   decl = se->expr;
+
+  /* Components can correspond to fields of different containing
+     types, as components are created without context, whereas
+     a concrete use of a component has the type of decl as context.
+     So, if the type doesn't match, we search the corresponding
+     FIELD_DECL in the parent type.  To not waste too much time
+     we cache this result in norestrict_decl.  */
+
+  if (DECL_FIELD_CONTEXT (field) != TREE_TYPE (decl))
+    {
+      int pass;
+      tree f2 = c->norestrict_decl;
+      for (pass = 0; pass < 2; pass++)
+	{
+	  if (!f2 || DECL_FIELD_CONTEXT (f2) != TREE_TYPE (decl))
+	    for (f2 = TYPE_FIELDS (TREE_TYPE (decl)); f2; f2 = DECL_CHAIN (f2))
+	      if (TREE_CODE (f2) == FIELD_DECL
+		  && DECL_NAME (f2) == DECL_NAME (field))
+		break;
+	  if (f2)
+	    break;
+	  gcc_assert (pass == 0);
+	  /* If we don't find the field it might be that
+	     we created a non-restrict variant while constructing the
+	     record type.  In that case the variant won't have all the fields
+	     yet.  Add the remaining ones and search again.  */
+	  mirror_fields (TREE_TYPE (decl), DECL_FIELD_CONTEXT (field));
+	}
+      gcc_assert (f2);
+      c->norestrict_decl = f2;
+      field = f2;
+    }
   tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
 			 decl, field, NULL_TREE);
 
Index: gfortran.h
===================================================================
--- gfortran.h	(revision 170097)
+++ gfortran.h	(working copy)
@@ -934,6 +934,10 @@ typedef struct gfc_component
   gfc_array_spec *as;
 
   tree backend_decl;
+  /* Used to cache a FIELD_DECL matching this same component
+     but applied to a different backend containing type that was
+     generated by gfc_nonrestricted_type.  */
+  tree norestrict_decl;
   locus loc;
   struct gfc_expr *initializer;
   struct gfc_component *next;
Index: trans-types.c
===================================================================
--- trans-types.c	(revision 170097)
+++ trans-types.c	(working copy)
@@ -1746,6 +1746,165 @@ gfc_build_pointer_type (gfc_symbol * sym
   else
     return build_pointer_type (type);
 }
+
+static tree gfc_nonrestricted_type (tree t);
+/* Given two record or union type nodes TO and FROM, ensure
+   that all fields in FROM have a corresponding field in TO,
+   their type being nonrestrict variants.  This accepts a TO
+   node that already has a prefix of the fields in FROM.  */
+void
+mirror_fields (tree to, tree from)
+{
+  tree fto, ffrom;
+  tree *chain;
+
+  /* Forward to the end of TOs fields.  */
+  fto = TYPE_FIELDS (to);
+  ffrom = TYPE_FIELDS (from);
+  chain = &TYPE_FIELDS (to);
+  while (fto)
+    {
+      gcc_assert (ffrom && DECL_NAME (fto) == DECL_NAME (ffrom));
+      chain = &DECL_CHAIN (fto);
+      fto = DECL_CHAIN (fto);
+      ffrom = DECL_CHAIN (ffrom);
+    }
+
+  /* Now add all fields remaining in FROM (starting with ffrom).  */
+  for (; ffrom; ffrom = DECL_CHAIN (ffrom))
+    {
+      tree newfield = copy_node (ffrom);
+      DECL_CONTEXT (newfield) = to;
+      /* The store to DECL_CHAIN might seem redundant with the
+	 stores to *chain, but not clearing it here would mean
+	 leaving a chain into the old fields.  If ever
+	 our called functions would look at them confusion
+	 will arise.  */
+      DECL_CHAIN (newfield) = NULL_TREE;
+      *chain = newfield;
+      chain = &DECL_CHAIN (newfield);
+
+      if (TREE_CODE (ffrom) == FIELD_DECL)
+	{
+	  tree elemtype = gfc_nonrestricted_type (TREE_TYPE (ffrom));
+	  TREE_TYPE (newfield) = elemtype;
+	}
+    }
+  *chain = NULL_TREE;
+}
+
+/* Given a type T, returns a different type of the same structure,
+   except that all types it refers to (recursively) are always
+   non-restrict qualified types.  */
+static tree
+gfc_nonrestricted_type (tree t)
+{
+  tree ret = t;
+  if (!TYPE_LANG_SPECIFIC (t))
+    TYPE_LANG_SPECIFIC (t)
+      = ggc_alloc_cleared_lang_type (sizeof (struct lang_type));
+  /* If we're dealing with this very node already further up
+     the call chain (recursion via pointers and struct members)
+     we haven't yet determined if we really need a new type node.
+     Assume we don't, return T itself.  */
+  if (TYPE_LANG_SPECIFIC (t)->nonrestricted_type == error_mark_node)
+    return t;
+
+  /* If we have calculated this all already, just return it.  */
+  if (TYPE_LANG_SPECIFIC (t)->nonrestricted_type)
+    return TYPE_LANG_SPECIFIC (t)->nonrestricted_type;
+
+  /* Mark this type.  */
+  TYPE_LANG_SPECIFIC (t)->nonrestricted_type = error_mark_node;
+
+  switch (TREE_CODE (t))
+    {
+      default:
+	break;
+
+      case POINTER_TYPE:
+      case REFERENCE_TYPE:
+	{
+	  tree totype = gfc_nonrestricted_type (TREE_TYPE (t));
+	  if (totype == TREE_TYPE (t))
+	    ret = t;
+	  else if (TREE_CODE (t) == POINTER_TYPE)
+	    ret = build_pointer_type (totype);
+	  else
+	    ret = build_reference_type (totype);
+	  ret = build_qualified_type (ret,
+				      TYPE_QUALS (t) & ~TYPE_QUAL_RESTRICT);
+	}
+	break;
+
+      case ARRAY_TYPE:
+	{
+	  tree elemtype = gfc_nonrestricted_type (TREE_TYPE (t));
+	  if (elemtype == TREE_TYPE (t))
+	    ret = t;
+	  else
+	    {
+	      ret = build_variant_type_copy (t);
+	      TREE_TYPE (ret) = elemtype;
+	      if (TYPE_LANG_SPECIFIC (t)
+		  && GFC_TYPE_ARRAY_DATAPTR_TYPE (t))
+		{
+		  tree dataptr_type = GFC_TYPE_ARRAY_DATAPTR_TYPE (t);
+		  dataptr_type = gfc_nonrestricted_type (dataptr_type);
+		  if (dataptr_type != GFC_TYPE_ARRAY_DATAPTR_TYPE (t))
+		    {
+		      TYPE_LANG_SPECIFIC (ret)
+			= ggc_alloc_cleared_lang_type (sizeof (struct
+							       lang_type));
+		      *TYPE_LANG_SPECIFIC (ret) = *TYPE_LANG_SPECIFIC (t);
+		      GFC_TYPE_ARRAY_DATAPTR_TYPE (ret) = dataptr_type;
+		    }
+		}
+	    }
+	}
+	break;
+
+      case RECORD_TYPE:
+      case UNION_TYPE:
+      case QUAL_UNION_TYPE:
+	{
+	  tree field;
+	  /* First determine if we need a new type at all.
+	     Careful, the two calls to gfc_nonrestricted_type per field
+	     might return different values.  That happens exactly when
+	     one of the fields reaches back to this very record type
+	     (via pointers).  The first calls will assume that we don't
+	     need to copy T (see the error_mark_node marking).  If there
+	     are any reasons for copying T apart from having to copy T,
+	     we'll indeed copy it, and the second calls to
+	     gfc_nonrestricted_type will use that new node if they
+	     reach back to T.  */
+	  for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
+	    if (TREE_CODE (field) == FIELD_DECL)
+	      {
+		tree elemtype = gfc_nonrestricted_type (TREE_TYPE (field));
+		if (elemtype != TREE_TYPE (field))
+		  break;
+	      }
+	  if (!field)
+	    break;
+	  ret = build_variant_type_copy (t);
+	  TYPE_FIELDS (ret) = NULL_TREE;
+
+	  /* Here we make sure that as soon as we know we have to copy
+	     T, that also fields reaching back to us will use the new
+	     copy.  It's okay if that copy still contains the old fields,
+	     we won't look at them.  */
+	  TYPE_LANG_SPECIFIC (t)->nonrestricted_type = ret;
+	  mirror_fields (ret, t);
+	}
+        break;
+    }
+
+  TYPE_LANG_SPECIFIC (t)->nonrestricted_type = ret;
+  return ret;
+}
+
 \f
 /* Return the type for a symbol.  Special handling is required for character
    types to get the correct level of indirection.
@@ -1796,6 +1955,9 @@ gfc_sym_type (gfc_symbol * sym)
 
   restricted = !sym->attr.target && !sym->attr.pointer
                && !sym->attr.proc_pointer && !sym->attr.cray_pointee;
+  if (!restricted)
+    type = gfc_nonrestricted_type (type);
+
   if (sym->attr.dimension)
     {
       if (gfc_is_nodesc_array (sym))
Index: trans.h
===================================================================
--- trans.h	(revision 170097)
+++ trans.h	(working copy)
@@ -571,6 +571,7 @@ tree gfc_builtin_function (tree);
 /* In trans-types.c.  */
 struct array_descr_info;
 bool gfc_get_array_descr_info (const_tree, struct array_descr_info *);
+void mirror_fields (tree, tree);
 
 /* In trans-openmp.c */
 bool gfc_omp_privatize_by_reference (const_tree);
@@ -700,6 +701,7 @@ struct GTY((variable_size))	lang_type	 {
   tree dataptr_type;
   tree span;
   tree base_decl[2];
+  tree nonrestricted_type;
 };
 
 struct GTY((variable_size)) lang_decl {
Index: testsuite/gfortran.dg/lto/pr45586_0.f90
===================================================================
--- testsuite/gfortran.dg/lto/pr45586_0.f90	(revision 0)
+++ testsuite/gfortran.dg/lto/pr45586_0.f90	(revision 0)
@@ -0,0 +1,29 @@
+! { dg-lto-do link }
+      MODULE M1
+      INTEGER, PARAMETER :: dp=8
+      TYPE realspace_grid_type
+
+          REAL(KIND=dp), DIMENSION ( :, :, : ), ALLOCATABLE :: r
+
+      END TYPE realspace_grid_type
+      END MODULE
+
+      MODULE M2
+      USE m1
+      CONTAINS
+      SUBROUTINE S1(x)
+      TYPE(realspace_grid_type), POINTER :: x
+      REAL(dp), DIMENSION(:, :, :), POINTER    :: y
+      y=>x%r
+      y=0
+
+      END SUBROUTINE
+      END MODULE
+
+      USE M2
+      TYPE(realspace_grid_type), POINTER :: x
+      ALLOCATE(x)
+      ALLOCATE(x%r(10,10,10))
+      CALL S1(x)
+      write(6,*) x%r
+      END

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

* Re: Fix PR45586 (type confusion ICEs), take 3
  2011-02-17 13:30   ` Fix PR45586 (type confusion ICEs), take 3 Michael Matz
@ 2011-02-17 19:40     ` Mikael Morin
  2011-02-17 22:31       ` Dominique Dhumieres
  2011-02-18 19:50       ` Fix PR45586 (type confusion ICEs), take 4 Michael Matz
  0 siblings, 2 replies; 7+ messages in thread
From: Mikael Morin @ 2011-02-17 19:40 UTC (permalink / raw)
  To: fortran; +Cc: Michael Matz, Dominique Dhumieres, gcc-patches, burnus

Hello,

On Thursday 17 February 2011 13:59:25 Michael Matz wrote:
> Hello,
> 
> On Tue, 15 Feb 2011, Michael Matz wrote:
> > On Mon, 14 Feb 2011, Dominique Dhumieres wrote:
> > > Michael,
> > > 
> > > With the patch take2, the test for pr47455 in comment #5
> > 
> > > ( http://gcc.gnu.org/bugzilla/attachment.cgi?id=23136 ) gives an ICE:
> > I see.  The underlying reason is that the type I construct a copy of
> > isn't yet layed out.  I'll fix that.
> 
> Was a bit more involved than I thought.  During construction of real class
> types (where members are function pointers, and those functions themself
> take a this argument of pointer to class) new fields are added to the
> record_type when we've already created the nonrestrict variant.  For that
> I've split out the field mirroring and use it in case we don't find the
> field we're searching for.  Additionally there was some problem with me
> using copy_node, I'm now using the more proper build_variant_type_copy.
> Otherwise patch is unchanged.
> 
> Regstrapped on x86_64-linux, no regressions.  I'm assuming that the
> testcase for pr47455 (typebound_proc_20.f90) goes into the tree when that
> bug is fixed for good, so I'm not adding it for this one.
Given how much time some of the bugs need to get fixed, I'm a bit inclined to 
commit the testcase as compile only test now. What do others think ?
(It's not much of a problem as long as we have Dominique around ;) )

> 
> Okay for trunk?
> 
> 
> Ciao,
> Michael.
> --
> fortran/
>         PR fortran/45586
>         * gfortran.h (struct gfc_component): Add norestrict_decl member.
>         * trans.h (mirror_fields): Declare function.
>         (struct lang_type): Add nonrestricted_type member.
>         * trans-expr.c (gfc_conv_component_ref): Search fields with correct
>         parent type.
>         * trans-types.c (mirror_fields, gfc_nonrestricted_type): New.
To respect the coding conventions, every non-static function should have a 
gfc_ prefix. That is, it should be:
        * trans-types.c (gfc_mirror_fields, nonrestricted_type): New. 

with callers updated (of course).

OK with that change.

Thanks again
Mikael


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

* Re: Fix PR45586 (type confusion ICEs), take 3
  2011-02-17 19:40     ` Mikael Morin
@ 2011-02-17 22:31       ` Dominique Dhumieres
  2011-02-18 19:50       ` Fix PR45586 (type confusion ICEs), take 4 Michael Matz
  1 sibling, 0 replies; 7+ messages in thread
From: Dominique Dhumieres @ 2011-02-17 22:31 UTC (permalink / raw)
  To: mikael.morin, fortran; +Cc: matz, gcc-patches, dominiq, burnus

Michael,

Sorry to be such a nuisance, but now the original test of pr47455
yields a segmentation fault:

Program received signal EXC_BAD_ACCESS, Could not access memory.
Reason: KERN_INVALID_ADDRESS at address: 0x0000000000000010
size_binop_loc (loc=1668, code=EXACT_DIV_EXPR, arg0=0x0, arg1=0x141d01410) at ../../work/gcc/fold-const.c:1427
1427	  tree type = TREE_TYPE (arg0);
(gdb) bt
#0  size_binop_loc (loc=1668, code=EXACT_DIV_EXPR, arg0=0x0, arg1=0x141d01410) at ../../work/gcc/fold-const.c:1427
#1  0x0000000100533a6e in gimplify_compound_lval (expr_p=0x141d3b270, pre_p=0x7fff5fbfd3c8, post_p=0x7fff5fbfcde0, fallback=1) at ../../work/gcc/gimplify.c:2043

> Given how much time some of the bugs need to get fixed, I'm a bit inclined to
> commit the testcase as compile only test now. What do others think ?

OK with a "TODO change compile to run when PR 47586 is fixed".

Dominique

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

* Re: Fix PR45586 (type confusion ICEs), take 4
  2011-02-17 19:40     ` Mikael Morin
  2011-02-17 22:31       ` Dominique Dhumieres
@ 2011-02-18 19:50       ` Michael Matz
  2011-02-18 20:47         ` Mikael Morin
  1 sibling, 1 reply; 7+ messages in thread
From: Michael Matz @ 2011-02-18 19:50 UTC (permalink / raw)
  To: Mikael Morin; +Cc: fortran, Dominique Dhumieres, gcc-patches, burnus

Hi,

On Thu, 17 Feb 2011, Mikael Morin wrote:

> > Regstrapped on x86_64-linux, no regressions.  I'm assuming that the
> > testcase for pr47455 (typebound_proc_20.f90) goes into the tree when that
> > bug is fixed for good, so I'm not adding it for this one.
> 
> Given how much time some of the bugs need to get fixed, I'm a bit 
> inclined to commit the testcase as compile only test now. What do others 
> think ? (It's not much of a problem as long as we have Dominique around 
> ;) )

Next iteration.  Still fixes the bug, but doesn't regress either test 
from pr47455 (thanks Dominique!).  I'm now deferring to build the variant 
until the input type really is final (has been layed out), otherwise some 
fields might still be missing (the one case of pr47455 == 
typebound_proc_20.f90), or at the very least the fields don't have their 
place (offset/size) yet (other case of pr47455 == typebound_proc_21.f90).

Now I also don't need to call mirror_fields from outside trans-types.c, 
hence made it static again, and not renamed to gfc_mirror_fields.  It's 
called only once, but I thought it be a good abstraction hence didn't fold 
it back into gfc_nonrestricted_type.

I've added both testcases that Dominique pointed out, as compile only.

Regstrapped on x86_64-linux, no regressions.  Let's see if Dominique finds 
another problem ;)  Otherwise okay for trunk?


Ciao,
Michael.
-- 
fortran/
	PR fortran/45586
	* gfortran.h (struct gfc_component): Add norestrict_decl member.
	* trans.h (struct lang_type): Add nonrestricted_type member.
	* trans-expr.c (gfc_conv_component_ref): Search fields with correct
	parent type.
	* trans-types.c (mirror_fields, gfc_nonrestricted_type): New.
	(gfc_sym_type): Use it.

testsuite/
	PR fortran/45586
	* gfortran.dg/lto/pr45586_0.f90: New test.
	* gfortran.dg/typebound_proc_20.f90: Ditto.
	* gfortran.dg/typebound_proc_21.f90: Ditto.

Index: trans-expr.c
===================================================================
--- trans-expr.c	(revision 170097)
+++ trans-expr.c	(working copy)
@@ -504,6 +504,26 @@ gfc_conv_component_ref (gfc_se * se, gfc
   field = c->backend_decl;
   gcc_assert (TREE_CODE (field) == FIELD_DECL);
   decl = se->expr;
+
+  /* Components can correspond to fields of different containing
+     types, as components are created without context, whereas
+     a concrete use of a component has the type of decl as context.
+     So, if the type doesn't match, we search the corresponding
+     FIELD_DECL in the parent type.  To not waste too much time
+     we cache this result in norestrict_decl.  */
+
+  if (DECL_FIELD_CONTEXT (field) != TREE_TYPE (decl))
+    {
+      tree f2 = c->norestrict_decl;
+      if (!f2 || DECL_FIELD_CONTEXT (f2) != TREE_TYPE (decl))
+	for (f2 = TYPE_FIELDS (TREE_TYPE (decl)); f2; f2 = DECL_CHAIN (f2))
+	  if (TREE_CODE (f2) == FIELD_DECL
+	      && DECL_NAME (f2) == DECL_NAME (field))
+	    break;
+      gcc_assert (f2);
+      c->norestrict_decl = f2;
+      field = f2;
+    }
   tmp = fold_build3_loc (input_location, COMPONENT_REF, TREE_TYPE (field),
 			 decl, field, NULL_TREE);
 
Index: gfortran.h
===================================================================
--- gfortran.h	(revision 170097)
+++ gfortran.h	(working copy)
@@ -934,6 +934,10 @@ typedef struct gfc_component
   gfc_array_spec *as;
 
   tree backend_decl;
+  /* Used to cache a FIELD_DECL matching this same component
+     but applied to a different backend containing type that was
+     generated by gfc_nonrestricted_type.  */
+  tree norestrict_decl;
   locus loc;
   struct gfc_expr *initializer;
   struct gfc_component *next;
Index: trans-types.c
===================================================================
--- trans-types.c	(revision 170097)
+++ trans-types.c	(working copy)
@@ -1746,6 +1746,171 @@ gfc_build_pointer_type (gfc_symbol * sym
   else
     return build_pointer_type (type);
 }
+
+static tree gfc_nonrestricted_type (tree t);
+/* Given two record or union type nodes TO and FROM, ensure
+   that all fields in FROM have a corresponding field in TO,
+   their type being nonrestrict variants.  This accepts a TO
+   node that already has a prefix of the fields in FROM.  */
+static void
+mirror_fields (tree to, tree from)
+{
+  tree fto, ffrom;
+  tree *chain;
+
+  /* Forward to the end of TOs fields.  */
+  fto = TYPE_FIELDS (to);
+  ffrom = TYPE_FIELDS (from);
+  chain = &TYPE_FIELDS (to);
+  while (fto)
+    {
+      gcc_assert (ffrom && DECL_NAME (fto) == DECL_NAME (ffrom));
+      chain = &DECL_CHAIN (fto);
+      fto = DECL_CHAIN (fto);
+      ffrom = DECL_CHAIN (ffrom);
+    }
+
+  /* Now add all fields remaining in FROM (starting with ffrom).  */
+  for (; ffrom; ffrom = DECL_CHAIN (ffrom))
+    {
+      tree newfield = copy_node (ffrom);
+      DECL_CONTEXT (newfield) = to;
+      /* The store to DECL_CHAIN might seem redundant with the
+	 stores to *chain, but not clearing it here would mean
+	 leaving a chain into the old fields.  If ever
+	 our called functions would look at them confusion
+	 will arise.  */
+      DECL_CHAIN (newfield) = NULL_TREE;
+      *chain = newfield;
+      chain = &DECL_CHAIN (newfield);
+
+      if (TREE_CODE (ffrom) == FIELD_DECL)
+	{
+	  tree elemtype = gfc_nonrestricted_type (TREE_TYPE (ffrom));
+	  TREE_TYPE (newfield) = elemtype;
+	}
+    }
+  *chain = NULL_TREE;
+}
+
+/* Given a type T, returns a different type of the same structure,
+   except that all types it refers to (recursively) are always
+   non-restrict qualified types.  */
+static tree
+gfc_nonrestricted_type (tree t)
+{
+  tree ret = t;
+
+  /* If the type isn't layed out yet, don't copy it.  If something
+     needs it for real it should wait until the type got finished.  */
+  if (!TYPE_SIZE (t))
+    return t;
+
+  if (!TYPE_LANG_SPECIFIC (t))
+    TYPE_LANG_SPECIFIC (t)
+      = ggc_alloc_cleared_lang_type (sizeof (struct lang_type));
+  /* If we're dealing with this very node already further up
+     the call chain (recursion via pointers and struct members)
+     we haven't yet determined if we really need a new type node.
+     Assume we don't, return T itself.  */
+  if (TYPE_LANG_SPECIFIC (t)->nonrestricted_type == error_mark_node)
+    return t;
+
+  /* If we have calculated this all already, just return it.  */
+  if (TYPE_LANG_SPECIFIC (t)->nonrestricted_type)
+    return TYPE_LANG_SPECIFIC (t)->nonrestricted_type;
+
+  /* Mark this type.  */
+  TYPE_LANG_SPECIFIC (t)->nonrestricted_type = error_mark_node;
+
+  switch (TREE_CODE (t))
+    {
+      default:
+	break;
+
+      case POINTER_TYPE:
+      case REFERENCE_TYPE:
+	{
+	  tree totype = gfc_nonrestricted_type (TREE_TYPE (t));
+	  if (totype == TREE_TYPE (t))
+	    ret = t;
+	  else if (TREE_CODE (t) == POINTER_TYPE)
+	    ret = build_pointer_type (totype);
+	  else
+	    ret = build_reference_type (totype);
+	  ret = build_qualified_type (ret,
+				      TYPE_QUALS (t) & ~TYPE_QUAL_RESTRICT);
+	}
+	break;
+
+      case ARRAY_TYPE:
+	{
+	  tree elemtype = gfc_nonrestricted_type (TREE_TYPE (t));
+	  if (elemtype == TREE_TYPE (t))
+	    ret = t;
+	  else
+	    {
+	      ret = build_variant_type_copy (t);
+	      TREE_TYPE (ret) = elemtype;
+	      if (TYPE_LANG_SPECIFIC (t)
+		  && GFC_TYPE_ARRAY_DATAPTR_TYPE (t))
+		{
+		  tree dataptr_type = GFC_TYPE_ARRAY_DATAPTR_TYPE (t);
+		  dataptr_type = gfc_nonrestricted_type (dataptr_type);
+		  if (dataptr_type != GFC_TYPE_ARRAY_DATAPTR_TYPE (t))
+		    {
+		      TYPE_LANG_SPECIFIC (ret)
+			= ggc_alloc_cleared_lang_type (sizeof (struct
+							       lang_type));
+		      *TYPE_LANG_SPECIFIC (ret) = *TYPE_LANG_SPECIFIC (t);
+		      GFC_TYPE_ARRAY_DATAPTR_TYPE (ret) = dataptr_type;
+		    }
+		}
+	    }
+	}
+	break;
+
+      case RECORD_TYPE:
+      case UNION_TYPE:
+      case QUAL_UNION_TYPE:
+	{
+	  tree field;
+	  /* First determine if we need a new type at all.
+	     Careful, the two calls to gfc_nonrestricted_type per field
+	     might return different values.  That happens exactly when
+	     one of the fields reaches back to this very record type
+	     (via pointers).  The first calls will assume that we don't
+	     need to copy T (see the error_mark_node marking).  If there
+	     are any reasons for copying T apart from having to copy T,
+	     we'll indeed copy it, and the second calls to
+	     gfc_nonrestricted_type will use that new node if they
+	     reach back to T.  */
+	  for (field = TYPE_FIELDS (t); field; field = DECL_CHAIN (field))
+	    if (TREE_CODE (field) == FIELD_DECL)
+	      {
+		tree elemtype = gfc_nonrestricted_type (TREE_TYPE (field));
+		if (elemtype != TREE_TYPE (field))
+		  break;
+	      }
+	  if (!field)
+	    break;
+	  ret = build_variant_type_copy (t);
+	  TYPE_FIELDS (ret) = NULL_TREE;
+
+	  /* Here we make sure that as soon as we know we have to copy
+	     T, that also fields reaching back to us will use the new
+	     copy.  It's okay if that copy still contains the old fields,
+	     we won't look at them.  */
+	  TYPE_LANG_SPECIFIC (t)->nonrestricted_type = ret;
+	  mirror_fields (ret, t);
+	}
+        break;
+    }
+
+  TYPE_LANG_SPECIFIC (t)->nonrestricted_type = ret;
+  return ret;
+}
+
 \f
 /* Return the type for a symbol.  Special handling is required for character
    types to get the correct level of indirection.
@@ -1796,6 +1961,9 @@ gfc_sym_type (gfc_symbol * sym)
 
   restricted = !sym->attr.target && !sym->attr.pointer
                && !sym->attr.proc_pointer && !sym->attr.cray_pointee;
+  if (!restricted)
+    type = gfc_nonrestricted_type (type);
+
   if (sym->attr.dimension)
     {
       if (gfc_is_nodesc_array (sym))
Index: trans.h
===================================================================
--- trans.h	(revision 170097)
+++ trans.h	(working copy)
@@ -700,6 +700,7 @@ struct GTY((variable_size))	lang_type	 {
   tree dataptr_type;
   tree span;
   tree base_decl[2];
+  tree nonrestricted_type;
 };
 
 struct GTY((variable_size)) lang_decl {
Index: testsuite/gfortran.dg/typebound_proc_20.f90
===================================================================
--- testsuite/gfortran.dg/typebound_proc_20.f90	(revision 0)
+++ testsuite/gfortran.dg/typebound_proc_20.f90	(revision 0)
@@ -0,0 +1,68 @@
+! { dg-do compile }
+! TODO: make runtime testcase once bug is fixed
+!
+! PR fortran/47455
+!
+! Based on an example by Thomas Henlich
+!
+
+module class_t
+    type :: tx
+        integer, dimension(:), allocatable :: i
+    end type tx
+    type :: t
+        type(tx), pointer :: x
+        type(tx) :: y
+    contains
+        procedure :: calc
+        procedure :: find_x
+        procedure :: find_y
+    end type t
+contains
+    subroutine calc(this)
+        class(t), target :: this
+        type(tx), target :: that
+        that%i = [1,2]
+        this%x => this%find_x(that, .true.)
+        if (associated (this%x)) call abort()
+        this%x => this%find_x(that, .false.)
+        if(any (this%x%i /= [5, 7])) call abort()
+        if (.not.associated (this%x,that)) call abort()
+        allocate(this%x)
+        if (associated (this%x,that)) call abort()
+        if (allocated(this%x%i)) call abort()
+        this%x = this%find_x(that, .false.)
+        that%i = [3,4]
+        if(any (this%x%i /= [5, 7])) call abort() ! FAILS
+
+        if (allocated (this%y%i)) call abort()
+        this%y = this%find_y()  ! FAILS
+        if (.not.allocated (this%y%i)) call abort()
+        if(any (this%y%i /= [6, 8])) call abort()
+    end subroutine calc
+    function find_x(this, that, l_null)
+       class(t), intent(in) :: this
+       type(tx), target  :: that
+       type(tx), pointer :: find_x
+       logical :: l_null
+       if (l_null) then
+         find_x => null()
+       else
+         find_x => that
+         that%i = [5, 7]
+       end if
+    end function find_x
+    function find_y(this) result(res)
+        class(t), intent(in) :: this
+        type(tx), allocatable :: res
+        allocate(res)
+        res%i = [6, 8]
+   end function find_y
+end module class_t
+
+use class_t
+type(t) :: x
+call x%calc()
+end
+
+! { dg-final { cleanup-modules "class_t" } }
Index: testsuite/gfortran.dg/typebound_proc_21.f90
===================================================================
--- testsuite/gfortran.dg/typebound_proc_21.f90	(revision 0)
+++ testsuite/gfortran.dg/typebound_proc_21.f90	(revision 0)
@@ -0,0 +1,27 @@
+! { dg-do compile }
+!
+! PR fortran/47455
+!
+module class_t
+    type :: tx
+        integer, dimension(:), allocatable :: i
+    end type tx
+    type :: t
+        type(tx), pointer :: x
+    contains
+        procedure :: calc
+        procedure :: find_x
+    end type t
+contains
+    subroutine calc(this)
+        class(t), target :: this
+        this%x = this%find_x()
+    end subroutine calc
+    function find_x(this)
+        class(t), intent(in) :: this
+        type(tx), pointer :: find_x
+        find_x => null()
+    end function find_x
+end module class_t
+
+! { dg-final { cleanup-modules "class_t" } }
Index: testsuite/gfortran.dg/lto/pr45586_0.f90
===================================================================
--- testsuite/gfortran.dg/lto/pr45586_0.f90	(revision 0)
+++ testsuite/gfortran.dg/lto/pr45586_0.f90	(revision 0)
@@ -0,0 +1,29 @@
+! { dg-lto-do link }
+      MODULE M1
+      INTEGER, PARAMETER :: dp=8
+      TYPE realspace_grid_type
+
+          REAL(KIND=dp), DIMENSION ( :, :, : ), ALLOCATABLE :: r
+
+      END TYPE realspace_grid_type
+      END MODULE
+
+      MODULE M2
+      USE m1
+      CONTAINS
+      SUBROUTINE S1(x)
+      TYPE(realspace_grid_type), POINTER :: x
+      REAL(dp), DIMENSION(:, :, :), POINTER    :: y
+      y=>x%r
+      y=0
+
+      END SUBROUTINE
+      END MODULE
+
+      USE M2
+      TYPE(realspace_grid_type), POINTER :: x
+      ALLOCATE(x)
+      ALLOCATE(x%r(10,10,10))
+      CALL S1(x)
+      write(6,*) x%r
+      END

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

* Re: Fix PR45586 (type confusion ICEs), take 4
  2011-02-18 19:50       ` Fix PR45586 (type confusion ICEs), take 4 Michael Matz
@ 2011-02-18 20:47         ` Mikael Morin
  0 siblings, 0 replies; 7+ messages in thread
From: Mikael Morin @ 2011-02-18 20:47 UTC (permalink / raw)
  To: Michael Matz; +Cc: fortran, Dominique Dhumieres, gcc-patches, burnus

On Friday 18 February 2011 20:11:07 Michael Matz wrote:
> Hi,
> 
> On Thu, 17 Feb 2011, Mikael Morin wrote:
> > > Regstrapped on x86_64-linux, no regressions.  I'm assuming that the
> > > testcase for pr47455 (typebound_proc_20.f90) goes into the tree when
> > > that bug is fixed for good, so I'm not adding it for this one.
> > 
> > Given how much time some of the bugs need to get fixed, I'm a bit
> > inclined to commit the testcase as compile only test now. What do others
> > think ? (It's not much of a problem as long as we have Dominique around
> > ;) )
> 
> Next iteration.  Still fixes the bug, but doesn't regress either test
> from pr47455 (thanks Dominique!).  I'm now deferring to build the variant
> until the input type really is final (has been layed out), otherwise some
> fields might still be missing (the one case of pr47455 ==
> typebound_proc_20.f90), or at the very least the fields don't have their
> place (offset/size) yet (other case of pr47455 == typebound_proc_21.f90).
> 
> Now I also don't need to call mirror_fields from outside trans-types.c,
> hence made it static again, and not renamed to gfc_mirror_fields.  It's
> called only once, but I thought it be a good abstraction hence didn't fold
> it back into gfc_nonrestricted_type.
> 
> I've added both testcases that Dominique pointed out, as compile only.
> 
> Regstrapped on x86_64-linux, no regressions.  Let's see if Dominique finds
> another problem ;)  Otherwise okay for trunk?
> 
Yes, OK
Dominique, we're holding our breath...

Mikael

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

end of thread, other threads:[~2011-02-18 19:50 UTC | newest]

Thread overview: 7+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2011-02-14 22:17 Fix PR45586 (type confusion ICEs), take 2 Dominique Dhumieres
2011-02-15 17:19 ` Michael Matz
2011-02-17 13:30   ` Fix PR45586 (type confusion ICEs), take 3 Michael Matz
2011-02-17 19:40     ` Mikael Morin
2011-02-17 22:31       ` Dominique Dhumieres
2011-02-18 19:50       ` Fix PR45586 (type confusion ICEs), take 4 Michael Matz
2011-02-18 20:47         ` Mikael Morin

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