Bug 43366

Summary: [OOP][F08] Intrinsic assign to polymorphic variable
Product: gcc Reporter: Tobias Burnus <burnus>
Component: fortranAssignee: Andre Vehreschild <vehre>
Status: RESOLVED FIXED    
Severity: normal CC: abensonca, anlauf, gcc-bugs, janus, mikael, pault
Priority: P3 Keywords: patch, rejects-valid
Version: 4.5.0   
Target Milestone: 7.0   
Host: Target:
Build: Known to work:
Known to fail: Last reconfirmed: 2010-08-03 11:23:14
Bug Depends on: 35810, 46321    
Bug Blocks: 39627    
Attachments: Small patch for the resolve.c. It misses all the real work (trans*.c).

Description Tobias Burnus 2010-03-14 14:00:32 UTC
Fortran 2003 has in Section 7.4.1.2:
"In an intrinsic assignment statement, variable shall not be polymorphic, and [...]"

Fortran 2008 has in Section 7.2.1.2

"If variable is a coindexed object, the variable
* shall not be polymorphic, [...]"

and the previous restriction has been removed.
Comment 1 Tobias Burnus 2010-03-14 14:01:35 UTC
See "Variable must not be polymorphic in assignment" in resolve.c and note that realloc on assignment must be supported to get this working properly (might already work for derived types).
Comment 2 janus 2010-08-03 11:23:14 UTC
(In reply to comment #1)
> note that realloc on assignment must be supported to get this working properly

... which is PR35810.
Comment 3 janus 2011-02-03 20:45:04 UTC
Test case:


type :: t
  integer :: i
end type

class(t), allocatable :: x
type(t) :: y = t (3)

x = y
print *,x%i
end
Comment 4 janus 2011-02-03 20:56:10 UTC
Here is a simple patch for getting rid of the error message:


Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c       (revision 169520)
+++ gcc/fortran/resolve.c       (working copy)
@@ -8879,15 +8879,13 @@ resolve_ordinary_assign (gfc_code *code, gfc_names
        gfc_current_ns->proc_name->attr.implicit_pure = 0;
     }
 
-  /* F03:7.4.1.2.  */
-  /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
-     and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
-  if (lhs->ts.type == BT_CLASS)
-    {
-      gfc_error ("Variable must not be polymorphic in assignment at %L",
-                &lhs->where);
-      return false;
-    }
+  /* F03:7.4.1.2, F08:7.2.1.2.  */
+  /* Valid in Fortran 2008, unless the LHS is both polymorphic and coindexed.  */
+  if (lhs->ts.type == BT_CLASS
+      && gfc_notify_std (GFC_STD_F2008,
+                        "Fortran 2008: Variable must not be polymorphic in "
+                        "assignment at %L", &lhs->where) == FAILURE)
+    return false;
 
   /* F2008, Section 7.2.1.2.  */
   if (gfc_is_coindexed (lhs) && gfc_has_ultimate_allocatable (lhs))
Comment 5 janus 2011-02-03 21:04:47 UTC
Realloc-on-assign for scalars was implemented in r169356.

Paul, what does it take to make this work for polymorphic scalars?
Comment 6 Tobias Burnus 2011-02-03 21:24:38 UTC
(In reply to comment #4)
> Here is a simple patch for getting rid of the error message:

The patch is not quite right. The LHS must be allocatable ("gfc_expr_attr(e).allocatable") - and it must not be coindexed ("!gfc_is_conindexed(e)").

Thus, you need something like:

if (lhs->ts.type == BT_CLASS)
  {
    if (gfc_expr_attr(e).allocatable") && !gfc_is_conindexed(e))

      if (gfc_notify_std(F2008 ...)  == FAILURE)
         return false;
    else
      {
        gfc_error ();
        return false;
      }
  }
Comment 7 Tobias Burnus 2011-02-03 21:28:10 UTC
(In reply to comment #4)
> Here is a simple patch for getting rid of the error message:

The patch is not quite right. The LHS must be allocatable and it must not be coindexed nor a coarray - otherwise, an intrinsic allocate is not allowed.

Cf. "7.2.1.2 Intrinsic assignment statement": "(1) if the variable is polymorphic it shall be allocatable and not a coarray," + quote in comment 0.

Thus, you need something like:

if (lhs->ts.type == BT_CLASS)
  {
    if (gfc_expr_attr(e).allocatable") && !gfc_is_coindexed(e)
        && !gfc_expr_attr(e).codimension)
      {
        if (gfc_notify_std(F2008 ...)  == FAILURE)
           return false;
      }
    else
      {
        gfc_error ();
        return false;
      }
  }
Comment 8 Tobias Burnus 2011-02-03 21:29:12 UTC
(In reply to comment #6)
Stupid firefox - it somehow must have submitted a draft. Ignore comment 6 and look at comment 7.
Comment 9 Paul Thomas 2011-02-04 09:32:01 UTC
(In reply to comment #5)
> Realloc-on-assign for scalars was implemented in r169356.
> 
> Paul, what does it take to make this work for polymorphic scalars?

Not a lot, I think.  If you take a look in gfc_trans_allocate, there is a bit that I think that you must have written, which initialises CLASS variables.  I would have thought that this can be lifted and deposited wholesale in trans_assignment1 and gfc_trans_allocate reconfigured to use the assignement.

I am taking a look at gfc_trans_allocate this lunchtime; there's something not quite right structurally with it.  I attempted to add a patch of code to have a single evaluation of the SOURCE expression and wound up displacing unrelated declarations, when I added the se.post to the end of the main block. gimple did not like it at all :-(  I'll come back to you.

Cheers

Paul
Comment 10 janus 2011-02-10 22:41:47 UTC
The following patch makes the test case in comment #3 work correctly:


Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(revision 169986)
+++ gcc/fortran/trans-expr.c	(working copy)
@@ -5838,6 +5838,14 @@ is_scalar_reallocatable_lhs (gfc_expr *expr)
 	&& !expr->ref)
     return true;
 
+  /* An allocatable class variable with no reference.  */
+  if (expr->symtree->n.sym->ts.type == BT_CLASS
+      && CLASS_DATA (expr->symtree->n.sym)->attr.allocatable
+      && expr->ref && expr->ref->type == REF_COMPONENT
+      && strcmp (expr->ref->u.c.component->name, "_data") == 0
+      && expr->ref->next == NULL)
+    return true;
+
   /* All that can be left are allocatable components.  */
   if ((expr->symtree->n.sym->ts.type != BT_DERIVED
 	&& expr->symtree->n.sym->ts.type != BT_CLASS)
Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(revision 169987)
+++ gcc/fortran/resolve.c	(working copy)
@@ -8881,14 +8881,32 @@ resolve_ordinary_assign (gfc_code *code, gfc_names
 	gfc_current_ns->proc_name->attr.implicit_pure = 0;
     }
 
-  /* F03:7.4.1.2.  */
-  /* FIXME: Valid in Fortran 2008, unless the LHS is both polymorphic
-     and coindexed; cf. F2008, 7.2.1.2 and PR 43366.  */
   if (lhs->ts.type == BT_CLASS)
     {
-      gfc_error ("Variable must not be polymorphic in assignment at %L",
-		 &lhs->where);
-      return false;
+      /* F08:7.2.1.2.  */
+      if (!gfc_expr_attr (lhs).allocatable)
+	{
+	  gfc_error ("Polymorphic variable in intrinsinc assignment must be "
+		     "allocatable at %L", &lhs->where);
+	  return false;
+	}
+      else if (gfc_expr_attr (lhs).codimension)
+	{
+	  gfc_error ("Polymorphic variable in intrinsinc assignment must not be"
+		     " coarray at %L", &lhs->where);
+	  return false;
+	}
+      else if (gfc_is_coindexed (lhs))
+	{
+	  gfc_error ("Polymorphic variable in intrinsinc assignment must not be"
+		     " coindexed at %L", &lhs->where);
+	  return false;
+	}
+      /* F03:7.4.1.2.  */
+      else if (gfc_notify_std (GFC_STD_F2008, "Fortran 2008: Variable must not "
+			       "be polymorphic in assignment at %L",
+			       &lhs->where) == FAILURE)
+	return false;
     }
 
   /* F2008, Section 7.2.1.2.  */
Comment 11 janus 2011-02-10 22:56:21 UTC
Stupid question, but shouldn't it be possible to replace the call to 'is_scalar_reallocatable_lhs' by a check for the allocatable attribute?


Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c    (revision 169986)
+++ gcc/fortran/trans-expr.c    (working copy)
@@ -6116,8 +6087,7 @@
   if (lss == gfc_ss_terminator)
     {
       /* F2003: Add the code for reallocation on assignment.  */
-      if (gfc_option.flag_realloc_lhs
-           && is_scalar_reallocatable_lhs (expr1))
+      if (gfc_option.flag_realloc_lhs && gfc_expr_attr (expr1).allocatable)
        alloc_scalar_allocatable_for_assignment (&block, rse.string_length,
                                                 expr1, expr2);


AFAICS, the routine does not do anything more anyway, right?
Comment 12 Tobias Burnus 2011-02-11 19:38:23 UTC
(In reply to comment #10)
> The following patch makes the test case in comment #3 work correctly:

I think your current patch only works if declared type (LHS) == effective type RHS. I think you need to use the size of the effective types ("_size"). The change should be in trans-expr.c's alloc_scalar_allocatable_for_assignment. Cf. "Determine allocate size" in trans-stmt.c's gfc_trans_allocate

(In reply to comment #11)
> Stupid question, but shouldn't it be possible to replace the call to
> 'is_scalar_reallocatable_lhs' by a check for the allocatable attribute?

I guess so - though I have not studied the code.
Comment 13 Tobias Burnus 2011-07-22 12:08:28 UTC
Regarding the LHS (in addition to comment 6):

- It may not be coindexed ("!gfc_is_conindexed(e)")
- It may not be a coarray ("!gfc_expr_attr (e).codimension")
- It may not have a coarray component ("!gfc_expr_attr (e).coarray_comp")

Cf. F2008, 7.2.1.2, item (1) and (3).
Comment 14 Tobias Burnus 2012-01-06 10:24:24 UTC
As litmus test: BT_CLASS version of PR 50981: Passing an unallocated/unassociated [or absent + nonpointer/nonallocatable] BT_CLASS variable or a unallocated/unassociated BT_CLASS component to an nonpointer/nonallocatable argument of an ELEMENTAL procedure.
Comment 15 Tobias Burnus 2012-02-09 17:48:11 UTC
Created attachment 26628 [details]
Small patch for the resolve.c. It misses all the real work (trans*.c).
Comment 16 Andrew Benson 2012-04-10 21:06:13 UTC
The following compiles with "-std=f2003" and runs successfully (using gfortran 4.8 r186145) with the "a=b" line in, but if I switch it for the "a%d=b%d" line I get a "Variable must not be polymorphic in intrinsic assignment at (1) - check that there is a matching specific subroutine for '=' operator" error:

module testMod
  implicit none
  public t
  type t
     integer :: i
  end type t
  type c
     class(t), allocatable :: d
  end type c
end module testMod

program testProg
  use testMod
  implicit none
  type(t) :: f
  type(c) :: a,b
  allocate(b%d,source=f)
  b%d%i=12345

  a=b      !! THIS COMPILES OK
!  a%d=b%d   !! THIS DOES NOT

  write (0,*) a%d%i
  write (0,*) b%d%i
end program testProg

Since "d" is polymorphic both should be disallowed with "-std=f2003" (and both allowed under F2008 I think).
Comment 17 Tobias Burnus 2013-09-18 18:14:59 UTC
Author: burnus
Date: Wed Sep 18 18:14:57 2013
New Revision: 202713

URL: http://gcc.gnu.org/viewcvs?rev=202713&root=gcc&view=rev
Log:
2013-09-15  Tobias Burnus  <burnus@net-b.de>

        PR fortran/43366
        * primary.c (gfc_variable_attr): Also handle codimension.
        * resolve.c (resolve_ordinary_assign): Add invalid-diagnostic
        * for
        polymorphic assignment.

2013-09-15  Tobias Burnus  <burnus@net-b.de>

        PR fortran/43366
        * gfortran.dg/class_39.f03: Update dg-error.
        * gfortran.dg/class_5.f03: Ditto.
        * gfortran.dg/class_53.f90: Ditto.
        * gfortran.dg/realloc_on_assign_20.f90: New.
        * gfortran.dg/realloc_on_assign_21.f90: New.
        * gfortran.dg/realloc_on_assign_22.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/realloc_on_assign_20.f90
    trunk/gcc/testsuite/gfortran.dg/realloc_on_assign_21.f90
    trunk/gcc/testsuite/gfortran.dg/realloc_on_assign_22.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/class_39.f03
    trunk/gcc/testsuite/gfortran.dg/class_5.f03
    trunk/gcc/testsuite/gfortran.dg/class_53.f90
Comment 18 Andre Vehreschild 2016-10-22 12:34:10 UTC
Author: vehre
Date: Sat Oct 22 12:33:38 2016
New Revision: 241439

URL: https://gcc.gnu.org/viewcvs?rev=241439&root=gcc&view=rev
Log:
gcc/fortran/ChangeLog:

2016-10-22  Andre Vehreschild  <vehre@gcc.gnu.org>

	PR fortran/43366
	PR fortran/51864
	PR fortran/57117
	PR fortran/61337
	PR fortran/61376
	* primary.c (gfc_expr_attr): For transformational functions on classes
	get the attrs from the class argument.
	* resolve.c (resolve_ordinary_assign): Remove error message due to
	feature implementation.  Rewrite POINTER_ASSIGNS to ordinary ones when
	the right-hand side is scalar class object (with some restrictions).
	* trans-array.c (trans_array_constructor): Create the temporary from
	class' inner type, i.e., the derived type.
	(build_class_array_ref): Add support for class array's storage of the
	class object or the array descriptor in the decl saved descriptor.
	(gfc_conv_expr_descriptor): When creating temporaries for class objects
	add the class object's handle into the decl saved descriptor.
	(structure_alloc_comps): Use the common way to get the _data component.
	(gfc_is_reallocatable_lhs): Add notion of allocatable class objects.
	* trans-expr.c (gfc_find_and_cut_at_last_class_ref): Remove the only ref
	only when the expression's type is BT_CLASS.
	(gfc_trans_class_init_assign): Correctly handle class arrays.
	(gfc_trans_class_assign): Joined into gfc_trans_assignment_1.
	(gfc_conv_procedure_call): Support for class types as arguments.
	(trans_get_upoly_len): For unlimited polymorphics retrieve the _len
	component's tree.
	(trans_class_vptr_len_assignment): Catch all ways to assign the _vptr
	and _len components of a class object correctly.
	(pointer_assignment_is_proc_pointer): Identify assignments of
	procedure pointers.
	(gfc_trans_pointer_assignment): Enhance support for class object pointer
	assignments.
	(gfc_trans_scalar_assign): Removed assert.
	(trans_class_assignment): Assign to a class object.
	(gfc_trans_assignment_1): Treat class objects correctly.
	(gfc_trans_assignment): Propagate flags to trans_assignment_1.
	* trans-stmt.c (gfc_trans_allocate): Use gfc_trans_assignment now
	instead of copy_class_to_class.
	* trans-stmt.h: Function prototype removed.
	* trans.c (trans_code): Less special casing for class objects.
	* trans.h: Added flags to gfc_trans_assignment () prototype.

gcc/testsuite/ChangeLog:

2016-10-22  Andre Vehreschild  <vehre@gcc.gnu.org>

        Forgot to add on original commit.
        * gfortran.dg/coarray_alloc_comp_2.f08: New test.

2016-10-22  Andre Vehreschild  <vehre@gcc.gnu.org>

	PR fortran/43366
	PR fortran/57117
	PR fortran/61337
	* gfortran.dg/alloc_comp_class_5.f03: New test.
	* gfortran.dg/class_allocate_21.f90: New test.
	* gfortran.dg/class_allocate_22.f90: New test.
	* gfortran.dg/realloc_on_assign_27.f08: New test.



Added:
    trunk/gcc/testsuite/gfortran.dg/alloc_comp_class_5.f03
    trunk/gcc/testsuite/gfortran.dg/class_allocate_21.f90
    trunk/gcc/testsuite/gfortran.dg/class_allocate_22.f90
    trunk/gcc/testsuite/gfortran.dg/coarray_alloc_comp_2.f08
    trunk/gcc/testsuite/gfortran.dg/realloc_on_assign_27.f08
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/primary.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans-stmt.h
    trunk/gcc/fortran/trans.c
    trunk/gcc/fortran/trans.h
    trunk/gcc/testsuite/ChangeLog
Comment 19 Andre Vehreschild 2016-10-24 16:59:02 UTC
Waiting one week for regression reports.
Comment 20 Andre Vehreschild 2016-11-08 12:59:44 UTC
No regressions reported so far. Closing.