summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/realloc_on_assign_28.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/realloc_on_assign_28.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/realloc_on_assign_28.f9040
1 files changed, 40 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/realloc_on_assign_28.f90 b/gcc/testsuite/gfortran.dg/realloc_on_assign_28.f90
new file mode 100644
index 00000000000..2e338e470fd
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/realloc_on_assign_28.f90
@@ -0,0 +1,40 @@
+! { dg-do run }
+!
+! PR fortran/66102
+!
+! Contributed by Vladimir Fuka <vladimir.fuka@gmail.com>
+!
+ type t
+ integer,allocatable :: i
+ end type
+
+ type(t) :: e
+ type(t), allocatable, dimension(:) :: a, b
+ integer :: chksum = 0
+
+ do i=1,3 ! Was 100 in original
+ e%i = i
+ chksum = chksum + i
+ if (.not.allocated(a)) then
+ a = [e]
+ b = first_arg([e], [e])
+ else
+ call foo
+ end if
+ end do
+
+ if (sum ([(a(i)%i, i=1,size(a))]) .ne. chksum) call abort
+ if (any([(a(i)%i, i=1,size(a))] /= [(i, i=1,size(a))])) call abort
+ if (size(a) /= size(b)) call abort
+ if (any([(b(i)%i, i=1,size(b))] /= [(i, i=1,size(b))])) call abort
+contains
+ subroutine foo
+ b = first_arg([b, e], [a, e])
+ a = [a, e]
+ end subroutine
+ elemental function first_arg(arg1, arg2)
+ type(t), intent(in) :: arg1, arg2
+ type(t) :: first_arg
+ first_arg = arg1
+ end function first_arg
+end