public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, Fortran] PR 41719: [OOP] invalid: Intrinsic assignment   involving polymorphic variables
@ 2009-10-16 20:58 Janus Weil
  2009-10-16 20:58 ` Tobias Burnus
  0 siblings, 1 reply; 3+ messages in thread
From: Janus Weil @ 2009-10-16 20:58 UTC (permalink / raw)
  To: gfortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 654 bytes --]

Hi all,

here is a small patch which fixes this PR (rather obvious). It was
successfully regtested on x86_64-unknown-linux-gnu.

As suggested by Tobias in comment #6, I'm ignoring the F08 std on this
matter for now, and just stick to F03.

Ok for trunk?

Cheers,
Janus



2009-10-16  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/41719
	* resolve.c (resolve_ordinary_assign): Reject intrinsic assignments
	to polymorphic variables.


2009-10-16  Janus Weil  <janus@gcc.gnu.org>

	PR fortran/41719
	* gfortran.dg/class_5.f03: New test case.
	* gfortran.dg/typebound_operator_2.f03: Fixing invalid test case.
	* gfortran.dg/typebound_operator_4.f03: Ditto.

[-- Attachment #2: pr41719.diff --]
[-- Type: text/x-diff, Size: 1772 bytes --]

Index: gcc/testsuite/gfortran.dg/typebound_operator_2.f03
===================================================================
--- gcc/testsuite/gfortran.dg/typebound_operator_2.f03	(Revision 152915)
+++ gcc/testsuite/gfortran.dg/typebound_operator_2.f03	(Arbeitskopie)
@@ -50,7 +50,6 @@ CONTAINS
   LOGICAL FUNCTION func (me, b) ! { dg-error "must be a SUBROUTINE" }
     CLASS(t), INTENT(OUT) :: me
     CLASS(t), INTENT(IN) :: b
-    me = t ()
     func = .TRUE.
   END FUNCTION func
 
Index: gcc/testsuite/gfortran.dg/typebound_operator_4.f03
===================================================================
--- gcc/testsuite/gfortran.dg/typebound_operator_4.f03	(Revision 152915)
+++ gcc/testsuite/gfortran.dg/typebound_operator_4.f03	(Arbeitskopie)
@@ -37,7 +37,7 @@ CONTAINS
   PURE SUBROUTINE assign_int (dest, from)
     CLASS(myint), INTENT(OUT) :: dest
     INTEGER, INTENT(IN) :: from
-    dest = myint (from)
+    dest%value = from
   END SUBROUTINE assign_int
 
   TYPE(myreal) FUNCTION add_real (a, b)
@@ -49,7 +49,7 @@ CONTAINS
   SUBROUTINE assign_real (dest, from)
     CLASS(myreal), INTENT(OUT) :: dest
     REAL, INTENT(IN) :: from
-    dest = myreal (from)
+    dest%value = from
   END SUBROUTINE assign_real
 
   SUBROUTINE in_module ()
Index: gcc/fortran/resolve.c
===================================================================
--- gcc/fortran/resolve.c	(Revision 152915)
+++ gcc/fortran/resolve.c	(Arbeitskopie)
@@ -7629,6 +7629,14 @@ resolve_ordinary_assign (gfc_code *code, gfc_names
 	}
     }
 
+  /* F03:7.4.1.2.  */
+  if (lhs->ts.type == BT_CLASS)
+    {
+      gfc_error ("Variable must not be polymorphic in assignment at %L",
+		 &lhs->where);
+      return false;
+    }
+
   gfc_check_assign (lhs, rhs, 1);
   return false;
 }

[-- Attachment #3: class_5.f03 --]
[-- Type: application/octet-stream, Size: 473 bytes --]

! { dg-do compile }
!
! PR 41719: [OOP] invalid: Intrinsic assignment involving polymorphic variables
!
! Contributed by Tobias Burnus <burnus@gcc.gnu.org>

 implicit none

 type t1
   integer :: a
 end type

 type, extends(t1) :: t2
   integer :: b
 end type

 class(t1),pointer :: cp
 type(t2) :: x

 x = t2(45,478)
 allocate(t2 :: cp)

 cp = x   ! { dg-error "Variable must not be polymorphic" }

 select type (cp)
 type is (t2)
   print *, cp%a, cp%b
 end select

end
 

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

* Re: [Patch, Fortran] PR 41719: [OOP] invalid: Intrinsic assignment    involving polymorphic variables
  2009-10-16 20:58 [Patch, Fortran] PR 41719: [OOP] invalid: Intrinsic assignment involving polymorphic variables Janus Weil
@ 2009-10-16 20:58 ` Tobias Burnus
  2009-10-16 21:29   ` Janus Weil
  0 siblings, 1 reply; 3+ messages in thread
From: Tobias Burnus @ 2009-10-16 20:58 UTC (permalink / raw)
  To: Janus Weil; +Cc: gfortran, gcc-patches

Janus Weil wrote:
> here is a small patch which fixes this PR (rather obvious). It was
> successfully regtested on x86_64-unknown-linux-gnu.
>
> Ok for trunk?
>
>   

Yes, the patch is okay. Thanks for the quick fix - and nice that you
spotted the difference in F2008. (F2008 allows it for allocatable
polymorphic variables; cf. F2003's (re)allocate on assignment for
nonpolymorphic allocatable variables.)

Tobias

> 2009-10-16  Janus Weil  <janus@gcc.gnu.org>
>
> 	PR fortran/41719
> 	* resolve.c (resolve_ordinary_assign): Reject intrinsic assignments
> 	to polymorphic variables.
>
>
> 2009-10-16  Janus Weil  <janus@gcc.gnu.org>
>
> 	PR fortran/41719
> 	* gfortran.dg/class_5.f03: New test case.
> 	* gfortran.dg/typebound_operator_2.f03: Fixing invalid test case.
> 	* gfortran.dg/typebound_operator_4.f03: Ditto.
>   

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

* Re: [Patch, Fortran] PR 41719: [OOP] invalid: Intrinsic assignment   involving polymorphic variables
  2009-10-16 20:58 ` Tobias Burnus
@ 2009-10-16 21:29   ` Janus Weil
  0 siblings, 0 replies; 3+ messages in thread
From: Janus Weil @ 2009-10-16 21:29 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gfortran, gcc-patches

2009/10/16 Tobias Burnus <burnus@net-b.de>:
> Janus Weil wrote:
>> here is a small patch which fixes this PR (rather obvious). It was
>> successfully regtested on x86_64-unknown-linux-gnu.
>>
>> Ok for trunk?
>>
>>
>
> Yes, the patch is okay.

Thanks. Committed as r152919.

Cheers,
Janus



>> 2009-10-16  Janus Weil  <janus@gcc.gnu.org>
>>
>>       PR fortran/41719
>>       * resolve.c (resolve_ordinary_assign): Reject intrinsic assignments
>>       to polymorphic variables.
>>
>>
>> 2009-10-16  Janus Weil  <janus@gcc.gnu.org>
>>
>>       PR fortran/41719
>>       * gfortran.dg/class_5.f03: New test case.
>>       * gfortran.dg/typebound_operator_2.f03: Fixing invalid test case.
>>       * gfortran.dg/typebound_operator_4.f03: Ditto.
>>
>
>

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

end of thread, other threads:[~2009-10-16 21:13 UTC | newest]

Thread overview: 3+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-10-16 20:58 [Patch, Fortran] PR 41719: [OOP] invalid: Intrinsic assignment involving polymorphic variables Janus Weil
2009-10-16 20:58 ` Tobias Burnus
2009-10-16 21:29   ` Janus Weil

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