aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/assign_13.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/assign_13.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/assign_13.f9025
1 files changed, 25 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/assign_13.f90 b/gcc/testsuite/gfortran.dg/assign_13.f90
new file mode 100644
index 0000000..262ade0
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/assign_13.f90
@@ -0,0 +1,25 @@
+! { dg-do run }
+!
+! PR fortran/121185
+! The assignment to Y%X in CHECK_T was using a polymorphic array access on the
+! left hand side, using the virtual table of Y.
+
+program p
+ implicit none
+ type t
+ complex, allocatable :: x(:)
+ end type t
+ real :: trace = 2.
+ type(t) :: z
+ z%x = [1,2] * trace
+ call check_t (z)
+contains
+ subroutine check_t (y)
+ class(t) :: y
+ ! print *, y% x
+ if (any(y%x /= [2., 4.])) error stop 11
+ y%x = y%x / trace
+ ! print *, y% x
+ if (any(y%x /= [1., 2.])) error stop 12
+ end subroutine
+end