]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
re PR fortran/78990 (ICE when assigning polymorphic array function result)
authorPaul Thomas <pault@gcc.gnu.org>
Sat, 3 Mar 2018 18:00:39 +0000 (18:00 +0000)
committerPaul Thomas <pault@gcc.gnu.org>
Sat, 3 Mar 2018 18:00:39 +0000 (18:00 +0000)
2018-03-03  Paul Thomas  <pault@gcc.gnu.org>

PR fortran/78990
* expr.c (gfc_is_class_array_function): Renamed from
'gfc_is_alloc_class_array_function' and modified to return true
for pointers as well as allocatable results.
* gfortran.h : Change of name for prototype of above function.
* trans-array.c (gfc_add_loop_ss_code): Force finalization of
class array results.
(build_class_array_ref): Change assertion into a condition.
(build_class_array_ref): Set the se class_vptr for class array
function results.
(gfc_walk_function_expr): Reference gfc_is_class_array_function
as above.
* trans-decl.c (get_proc_result): Move it up before
gfc_trans_deferred_vars.
(gfc_trans_deferred_vars): Nullify explicit return class arrays
on entry.
* trans-expr.c (gfc_conv_class_to_class): Allow conversion of
class array functions that have an se class_vptr and use it
for the result vptr.
(gfc_conv_subref_array_arg): Rename reference to the above
function.
(gfc_conv_procedure_call): Ditto. Add the se pre block to the
loop pre block before the function is evaluated. Do not
finalize class pointer results.
(arrayfunc_assign_needs_temporary, gfc_trans_assignment_1) More
renamed references.
* trans-intrinsic.c (gfc_conv_intrinsic_size): Ditto.

2018-03-03  Paul Thomas  <pault@gcc.gnu.org>

PR fortran/78990
* gfortran.dg/class_67.f90: New test.

From-SVN: r258217

gcc/fortran/ChangeLog
gcc/fortran/expr.c
gcc/fortran/gfortran.h
gcc/fortran/resolve.c
gcc/fortran/trans-array.c
gcc/fortran/trans-decl.c
gcc/fortran/trans-expr.c
gcc/fortran/trans-intrinsic.c
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/class_67.f90 [new file with mode: 0644]

index 9eec89572449e4a7733c14671e1154c1974f9eca..4196cf88c623de72c6255c0447e39072e9d90f24 100644 (file)
@@ -1,3 +1,34 @@
+2018-03-03  Paul Thomas  <pault@gcc.gnu.org>
+
+       Backport from trunk.
+       PR fortran/78990
+       * expr.c (gfc_is_class_array_function): Renamed from
+       'gfc_is_alloc_class_array_function' and modified to return true
+       for pointers as well as allocatable results.
+       * gfortran.h : Change of name for prototype of above function.
+       * trans-array.c (gfc_add_loop_ss_code): Force finalization of
+       class array results.
+       (build_class_array_ref): Change assertion into a condition.
+       (build_class_array_ref): Set the se class_vptr for class array
+       function results.
+       (gfc_walk_function_expr): Reference gfc_is_class_array_function
+       as above.
+       * trans-decl.c (get_proc_result): Move it up before
+       gfc_trans_deferred_vars.
+       (gfc_trans_deferred_vars): Nullify explicit return class arrays
+       on entry.
+       * trans-expr.c (gfc_conv_class_to_class): Allow conversion of
+       class array functions that have an se class_vptr and use it
+       for the result vptr.
+       (gfc_conv_subref_array_arg): Rename reference to the above
+       function.
+       (gfc_conv_procedure_call): Ditto. Add the se pre block to the
+       loop pre block before the function is evaluated. Do not
+       finalize class pointer results.
+       (arrayfunc_assign_needs_temporary, gfc_trans_assignment_1) More
+       renamed references.
+       * trans-intrinsic.c (gfc_conv_intrinsic_size): Ditto.
+
 2018-02-25  Steven G. Kargl  <kargl@gcc.gnu.org>
 
        PR fortran/83633
index a30ea2d3d54f54dbfe79b46c7d2a6cd41783b94a..aceefb6e110f584ad087ef5a919b2a7660d4ca43 100644 (file)
@@ -4348,14 +4348,15 @@ gfc_is_alloc_class_scalar_function (gfc_expr *expr)
 /* Determine if an expression is a function with an allocatable class array
    result.  */
 bool
-gfc_is_alloc_class_array_function (gfc_expr *expr)
+gfc_is_class_array_function (gfc_expr *expr)
 {
   if (expr->expr_type == EXPR_FUNCTION
       && expr->value.function.esym
       && expr->value.function.esym->result
       && expr->value.function.esym->result->ts.type == BT_CLASS
       && CLASS_DATA (expr->value.function.esym->result)->attr.dimension
-      && CLASS_DATA (expr->value.function.esym->result)->attr.allocatable)
+      && (CLASS_DATA (expr->value.function.esym->result)->attr.allocatable
+         || CLASS_DATA (expr->value.function.esym->result)->attr.pointer))
     return true;
 
   return false;
index 0bb71cb184d195842ebcc12a8cd5358e56f28423..4e08449d2a3eef2b4bf4724e98b3c391e136335c 100644 (file)
@@ -3057,7 +3057,7 @@ bool gfc_expr_check_typed (gfc_expr*, gfc_namespace*, bool);
 gfc_component * gfc_get_proc_ptr_comp (gfc_expr *);
 bool gfc_is_proc_ptr_comp (gfc_expr *);
 bool gfc_is_alloc_class_scalar_function (gfc_expr *);
-bool gfc_is_alloc_class_array_function (gfc_expr *);
+bool gfc_is_class_array_function (gfc_expr *);
 
 bool gfc_ref_this_image (gfc_ref *ref);
 bool gfc_is_coindexed (gfc_expr *);
index 84600bd959cd66abcbf91accec294c06cf27999c..d2d1b5835356d8e66e15eeff26712819a2c7ebe3 100644 (file)
@@ -8344,6 +8344,9 @@ resolve_select_type (gfc_code *code, gfc_namespace *old_ns)
        code->expr1->symtree->n.sym->ts = code->expr2->ts;
       selector_type = CLASS_DATA (code->expr2)->ts.u.derived;
 
+      if (code->expr2->rank && CLASS_DATA (code->expr1)->as)
+       CLASS_DATA (code->expr1)->as->rank = code->expr2->rank;
+
       /* F2008: C803 The selector expression must not be coindexed.  */
       if (gfc_is_coindexed (code->expr2))
        {
index b1a07f5defd2b731b019c2779b3f5cf268b51ff2..c9ed95bbd9ff4e268fd4f989480458b5b4da5f46 100644 (file)
@@ -2615,6 +2615,8 @@ gfc_add_loop_ss_code (gfc_loopinfo * loop, gfc_ss * ss, bool subscript,
          gfc_init_se (&se, NULL);
          se.loop = loop;
          se.ss = ss;
+         if (gfc_is_class_array_function (expr))
+           expr->must_finalize = 1;
          gfc_conv_expr (&se, expr);
          gfc_add_block_to_block (&outer_loop->pre, &se.pre);
          gfc_add_block_to_block (&outer_loop->post, &se.post);
@@ -3045,7 +3047,7 @@ build_class_array_ref (gfc_se *se, tree base, tree index)
 
   if (expr == NULL
       || (expr->ts.type != BT_CLASS
-         && !gfc_is_alloc_class_array_function (expr)))
+         && !gfc_is_class_array_function (expr)))
     return false;
 
   if (expr->symtree && expr->symtree->n.sym->ts.type == BT_CLASS)
@@ -3074,12 +3076,12 @@ build_class_array_ref (gfc_se *se, tree base, tree index)
     return false;
 
   if (class_ref == NULL && expr->symtree->n.sym->attr.function
-      && expr->symtree->n.sym == expr->symtree->n.sym->result)
+      && expr->symtree->n.sym == expr->symtree->n.sym->result
+      && expr->symtree->n.sym->backend_decl == current_function_decl)
     {
-      gcc_assert (expr->symtree->n.sym->backend_decl == current_function_decl);
       decl = gfc_get_fake_result_decl (expr->symtree->n.sym, 0);
     }
-  else if (gfc_is_alloc_class_array_function (expr))
+  else if (gfc_is_class_array_function (expr))
     {
       size = NULL_TREE;
       decl = NULL_TREE;
@@ -3102,6 +3104,8 @@ build_class_array_ref (gfc_se *se, tree base, tree index)
 
       if (decl == NULL_TREE)
        return false;
+
+      se->class_vptr = gfc_evaluate_now (gfc_class_vptr_get (decl), &se->pre);
     }
   else if (class_ref == NULL)
     {
@@ -9537,7 +9541,7 @@ gfc_walk_function_expr (gfc_ss * ss, gfc_expr * expr)
   if (!sym)
     sym = expr->symtree->n.sym;
 
-  if (gfc_is_alloc_class_array_function (expr))
+  if (gfc_is_class_array_function (expr))
     return gfc_get_array_ss (ss, expr,
                             CLASS_DATA (expr->value.function.esym->result)->as->rank,
                             GFC_SS_FUNCTION);
index 36f882029e21e0c67546d536094d9e6aaf138be0..7b30380f50a1060aeedaf221731ff711ef6bb08d 100644 (file)
@@ -4007,6 +4007,24 @@ gfc_null_and_pass_deferred_len (gfc_symbol *sym, stmtblock_t *init,
   return tmp;
 }
 
+
+/* Get the result expression for a procedure.  */
+
+static tree
+get_proc_result (gfc_symbol* sym)
+{
+  if (sym->attr.subroutine || sym == sym->result)
+    {
+      if (current_fake_result_decl != NULL)
+       return TREE_VALUE (current_fake_result_decl);
+
+      return NULL_TREE;
+    }
+
+  return sym->result->backend_decl;
+}
+
+
 /* Generate function entry and exit code, and add it to the function body.
    This includes:
     Allocation and initialization of array variables.
@@ -4116,6 +4134,21 @@ gfc_trans_deferred_vars (gfc_symbol * proc_sym, gfc_wrapped_block * block)
       else
        gcc_assert (flag_f2c && proc_sym->ts.type == BT_COMPLEX);
     }
+  else if (proc_sym == proc_sym->result && IS_CLASS_ARRAY (proc_sym))
+    {
+      /* Nullify explicit return class arrays on entry.  */
+      tree type;
+      tmp = get_proc_result (proc_sym);
+       if (tmp && GFC_CLASS_TYPE_P (TREE_TYPE (tmp)))
+         {
+           gfc_start_block (&init);
+           tmp = gfc_class_data_get (tmp);
+           type = TREE_TYPE (gfc_conv_descriptor_data_get (tmp));
+           gfc_conv_descriptor_data_set (&init, tmp, build_int_cst (type, 0));
+           gfc_add_init_cleanup (block, gfc_finish_block (&init), NULL_TREE);
+         }
+    }
+
 
   /* Initialize the INTENT(OUT) derived type dummy arguments.  This
      should be done here so that the offsets and lbounds of arrays
@@ -5830,23 +5863,6 @@ create_main_function (tree fndecl)
 }
 
 
-/* Get the result expression for a procedure.  */
-
-static tree
-get_proc_result (gfc_symbol* sym)
-{
-  if (sym->attr.subroutine || sym == sym->result)
-    {
-      if (current_fake_result_decl != NULL)
-       return TREE_VALUE (current_fake_result_decl);
-
-      return NULL_TREE;
-    }
-
-  return sym->result->backend_decl;
-}
-
-
 /* Generate an appropriate return-statement for a procedure.  */
 
 tree
index f1b7bfd9d6b1c1fb41255bfcc3a044748cc4672f..f72503bd98355a1f5b052112d26dc195df4118b4 100644 (file)
@@ -890,6 +890,7 @@ gfc_conv_class_to_class (gfc_se *parmse, gfc_expr *e, gfc_typespec class_ts,
     }
 
   if ((ref == NULL || class_ref == ref)
+      && !(gfc_is_class_array_function (e) && parmse->class_vptr != NULL_TREE)
       && (!class_ts.u.derived->components->as
          || class_ts.u.derived->components->as->rank != -1))
     return;
@@ -960,8 +961,11 @@ gfc_conv_class_to_class (gfc_se *parmse, gfc_expr *e, gfc_typespec class_ts,
      First we have to find the corresponding class reference.  */
 
   tmp = NULL_TREE;
-  if (class_ref == NULL
-       && e->symtree && e->symtree->n.sym->ts.type == BT_CLASS)
+  if (gfc_is_class_array_function (e)
+      && parmse->class_vptr != NULL_TREE)
+    tmp = parmse->class_vptr;
+  else if (class_ref == NULL
+          && e->symtree && e->symtree->n.sym->ts.type == BT_CLASS)
     {
       tmp = e->symtree->n.sym->backend_decl;
       if (DECL_LANG_SPECIFIC (tmp) && GFC_DECL_SAVED_DESCRIPTOR (tmp))
@@ -988,7 +992,11 @@ gfc_conv_class_to_class (gfc_se *parmse, gfc_expr *e, gfc_typespec class_ts,
   if (TREE_CODE (TREE_TYPE (tmp)) == REFERENCE_TYPE)
     tmp = build_fold_indirect_ref_loc (input_location, tmp);
 
-  vptr = gfc_class_vptr_get (tmp);
+  if (!(gfc_is_class_array_function (e) && parmse->class_vptr))
+    vptr = gfc_class_vptr_get (tmp);
+  else
+    vptr = tmp;
+
   gfc_add_modify (&block, ctree,
                  fold_convert (TREE_TYPE (ctree), vptr));
 
@@ -2348,7 +2356,7 @@ gfc_conv_component_ref (gfc_se * se, gfc_ref * ref)
      On the other hand, if the context is a UNION or a MAP (a
      RECORD_TYPE within a UNION_TYPE) always use the given FIELD_DECL.  */
 
-  if (context != TREE_TYPE (decl) 
+  if (context != TREE_TYPE (decl)
       && !(   TREE_CODE (TREE_TYPE (field)) == UNION_TYPE /* Field is union */
            || TREE_CODE (context) == UNION_TYPE))         /* Field is map */
     {
@@ -4407,7 +4415,7 @@ gfc_conv_subref_array_arg (gfc_se * parmse, gfc_expr * expr, int g77,
   /* Reset the offset for the function call since the loop
      is zero based on the data pointer.  Note that the temp
      comes first in the loop chain since it is added second.  */
-  if (gfc_is_alloc_class_array_function (expr))
+  if (gfc_is_class_array_function (expr))
     {
       tmp = loop.ss->loop_chain->info->data.array.descriptor;
       gfc_conv_descriptor_offset_set (&loop.pre, tmp,
@@ -4456,7 +4464,7 @@ gfc_conv_subref_array_arg (gfc_se * parmse, gfc_expr * expr, int g77,
   dimen = rse.ss->dimen;
 
   /* Skip the write-out loop for this case.  */
-  if (gfc_is_alloc_class_array_function (expr))
+  if (gfc_is_class_array_function (expr))
     goto class_array_fcn;
 
   /* Calculate the bounds of the scalarization.  */
@@ -4749,7 +4757,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
              gcc_assert ((!comp && gfc_return_by_reference (sym)
                           && sym->result->attr.dimension)
                          || (comp && comp->attr.dimension)
-                         || gfc_is_alloc_class_array_function (expr));
+                         || gfc_is_class_array_function (expr));
              gcc_assert (se->loop != NULL);
              /* Access the previously obtained result.  */
              gfc_conv_tmp_array_ref (se);
@@ -5402,7 +5410,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
                                fsym ? fsym->attr.intent : INTENT_INOUT,
                                fsym && fsym->attr.pointer);
 
-             else if (gfc_is_alloc_class_array_function (e)
+             else if (gfc_is_class_array_function (e)
                         && fsym && fsym->ts.type == BT_DERIVED)
                /* See previous comment.  For function actual argument,
                   the write out is not needed so the intent is set as
@@ -6191,7 +6199,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
         call the finalization function of the temporary. Note that the
         nullification of allocatable components needed by the result
         is done in gfc_trans_assignment_1.  */
-      if (expr && ((gfc_is_alloc_class_array_function (expr)
+      if (expr && ((gfc_is_class_array_function (expr)
                    && se->ss && se->ss->loop)
                   || gfc_is_alloc_class_scalar_function (expr))
          && se->expr && GFC_CLASS_TYPE_P (TREE_TYPE (se->expr))
@@ -6202,6 +6210,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
          int n;
          if (se->ss && se->ss->loop)
            {
+             gfc_add_block_to_block (&se->ss->loop->pre, &se->pre);
              se->expr = gfc_evaluate_now (se->expr, &se->ss->loop->pre);
              tmp = gfc_class_data_get (se->expr);
              info->descriptor = tmp;
@@ -6224,6 +6233,11 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
                        CLASS_DATA (expr->value.function.esym->result)->attr);
            }
 
+         if ((gfc_is_class_array_function (expr)
+              || gfc_is_alloc_class_scalar_function (expr))
+             && CLASS_DATA (expr->value.function.esym->result)->attr.pointer)
+           goto no_finalization;
+
          final_fndecl = gfc_class_vtab_final_get (se->expr);
          is_final = fold_build2_loc (input_location, NE_EXPR,
                                      boolean_type_node,
@@ -6254,6 +6268,8 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
              tmp = gfc_call_free (tmp);
              gfc_add_expr_to_block (&se->post, tmp);
            }
+
+no_finalization:
          expr->must_finalize = 0;
        }
 
@@ -8392,7 +8408,7 @@ arrayfunc_assign_needs_temporary (gfc_expr * expr1, gfc_expr * expr2)
   gfc_symbol *sym = expr1->symtree->n.sym;
 
   /* Play it safe with class functions assigned to a derived type.  */
-  if (gfc_is_alloc_class_array_function (expr2)
+  if (gfc_is_class_array_function (expr2)
       && expr1->ts.type == BT_DERIVED)
     return true;
 
@@ -9271,7 +9287,7 @@ gfc_trans_assignment_1 (gfc_expr * expr1, gfc_expr * expr2, bool init_flag,
   rss = NULL;
 
   if ((expr1->ts.type == BT_DERIVED)
-      && (gfc_is_alloc_class_array_function (expr2)
+      && (gfc_is_class_array_function (expr2)
          || gfc_is_alloc_class_scalar_function (expr2)))
     expr2->must_finalize = 1;
 
@@ -9442,9 +9458,9 @@ gfc_trans_assignment_1 (gfc_expr * expr1, gfc_expr * expr2, bool init_flag,
      nullification occurs before the call to the finalizer. In the case of
      a scalar to array assignment, this is done in gfc_trans_scalar_assign
      as part of the deep copy.  */
-  if (!scalar_to_array && (expr1->ts.type == BT_DERIVED)
-                                             && (gfc_is_alloc_class_array_function (expr2)
-                                                     || gfc_is_alloc_class_scalar_function (expr2)))
+  if (!scalar_to_array
+      && (expr1->ts.type == BT_DERIVED)
+      && (gfc_is_class_array_function (expr2) || gfc_is_alloc_class_scalar_function (expr2)))
     {
       tmp = rse.expr;
       tmp = gfc_nullify_alloc_comp (expr1->ts.u.derived, rse.expr, 0);
index e0ecc3d902d6517c33bff9963d793bf005f74df5..bad959bda88ca57b3423731e7b4aac3dd6663bbe 100644 (file)
@@ -5832,7 +5832,7 @@ gfc_conv_intrinsic_size (gfc_se * se, gfc_expr * expr)
     gfc_add_class_array_ref (actual->expr);
 
   argse.data_not_needed = 1;
-  if (gfc_is_alloc_class_array_function (actual->expr))
+  if (gfc_is_class_array_function (actual->expr))
     {
       /* For functions that return a class array conv_expr_descriptor is not
         able to get the descriptor right.  Therefore this special case.  */
index e2c0b7a613510474fcd04dfee8c4fa11a25c235f..f562bccf7442206ae13f2fff804f5a3d6621b138 100644 (file)
@@ -1,3 +1,9 @@
+2018-03-03  Paul Thomas  <pault@gcc.gnu.org>
+
+       Backport from trunk.
+       PR fortran/78990
+       * gfortran.dg/class_67.f90: New test.
+
 2017-03-02  Thomas Schwinge  <thomas@codesourcery.com>
 
        Backport from trunk r256891:
diff --git a/gcc/testsuite/gfortran.dg/class_67.f90 b/gcc/testsuite/gfortran.dg/class_67.f90
new file mode 100644 (file)
index 0000000..2002993
--- /dev/null
@@ -0,0 +1,55 @@
+! { dg-do run }
+!
+! Test the fix for PR78990 in which the scalarization of the assignment
+! in the main program failed for two reasons: (i) The conversion of 'v1'
+! into a class actual was being done after the call to 'return_t1', giving
+! rise to the ICE reported in comment #1; and (ii) The 'info' descriptor,
+! required for scalarization was not set, which gave rise to the ICE noted
+! by the contributor.
+!
+! Contributed by Chris Macmackin  <cmacmackin@gmail.com>
+!
+module test_type
+  implicit none
+
+  type t1
+     integer :: i
+   contains
+     procedure :: assign
+     generic :: assignment(=) => assign
+  end type t1
+
+contains
+
+  elemental subroutine assign(this,rhs)
+    class(t1), intent(inout) :: this
+    class(t1), intent(in) :: rhs
+    this%i = rhs%i
+  end subroutine assign
+
+  function return_t1(arg)
+    class(t1), dimension(:), intent(in) :: arg
+    class(t1), dimension(:), allocatable :: return_t1
+    allocate(return_t1(size(arg)), source=arg)
+  end function return_t1
+
+  function return_t1_p(arg)
+    class(t1), dimension(:), intent(in), target :: arg
+    class(t1), dimension(:), pointer :: return_t1_p
+    return_t1_p => arg
+  end function return_t1_p
+end module test_type
+
+program test
+  use test_type
+  implicit none
+
+  type(t1), dimension(3) :: v1, v2
+  v1%i = [1,2,3]
+  v2 = return_t1(v1)
+  if (any (v2%i .ne. v1%i)) call abort
+
+  v1%i = [4,5,6]
+  v2 = return_t1_p(v1)
+  if (any (v2%i .ne. v1%i)) call abort
+end program test