c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / allocatable_function_10.f90
blob2f93bb0f841d72593832f90d6f9eedae60bfb10b
1 ! { dg-do run }
3 ! Test the fix for PR78293. The deallocations are present at the
4 ! end of the main programme to aid memory leak searching. The
5 ! allocation in 'tt' leaked memory from an intermediate temporary
6 ! for the array constructor.
8 ! Contributed by Andrew Benson <abensonca@gmail.com>
10 module m
11 implicit none
13 type t
14 integer, allocatable, dimension(:) :: r
15 end type t
17 contains
19 function tt(a,b)
20 implicit none
21 type(t), allocatable, dimension(:) :: tt
22 type(t), intent(in), dimension(:) :: a,b
23 allocate(tt, source = [a,b])
24 end function tt
26 function ts(arg)
27 implicit none
28 type(t), allocatable, dimension(:) :: ts
29 integer, intent(in) :: arg(:)
30 allocate(ts(1))
31 allocate(ts(1)%r, source = arg)
32 return
33 end function ts
35 end module m
37 program p
38 use m
39 implicit none
40 type(t), dimension(2) :: c
41 c=tt(ts([99,199,1999]),ts([42,142]))
42 if (any (c(1)%r .ne. [99,199,1999])) STOP 1
43 if (any (c(2)%r .ne. [42,142])) STOP 2
44 deallocate(c(1)%r)
45 deallocate(c(2)%r)
46 end program p