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.
git-svn-id: svn+ssh://gcc.gnu.org/svn/gcc/trunk@152919
138bc75d-0d04-0410-961f-
82ee72b054a4
+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 Paul Thomas <pault@gcc.gnu.org>
PR fortran/41648
}
}
+ /* 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;
}
+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.
+
2009-10-16 Kaveh R. Ghazi <ghazi@caip.rutgers.edu>
* g++.dg/ipa/iinline-1.C: Use dg-add-options bind_pic_locally.
--- /dev/null
+! { 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
+
\ No newline at end of file
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
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)
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 ()