lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / alloc_comp_result_2.f90
blob2e907e3155857c6f1935fed5dc00d1ec60d8bf6d
1 ! Tests the fix for PR40440, in which gfortran tried to deallocate
2 ! the allocatable components of the actual argument of CALL SUB
4 ! Contributed by Juergen Reuter <juergen.reuter@desy.de>
5 ! Reduced testcase from Tobias Burnus <burnus@gcc.gnu.org>
7 implicit none
8 type t
9 integer, allocatable :: A(:)
10 end type t
11 type (t) :: arg
12 arg = t ([1,2,3])
13 call sub (func (arg))
14 contains
15 function func (a)
16 type(t), pointer :: func
17 type(t), target :: a
18 integer, save :: i = 0
19 if (i /= 0) STOP 1! multiple calls would cause this abort
20 i = i + 1
21 func => a
22 end function func
23 subroutine sub (a)
24 type(t), intent(IN), target :: a
25 if (any (a%A .ne. [1,2,3])) STOP 2
26 end subroutine sub
27 end