1! { dg-do compile }
2! { dg-options "-fdump-tree-original" }
3!
4! Test the fix for PR66082. The original problem was with the first
5! call foo_1d.
6!
7! Reported by Damian Rouson  <damian@sourceryinstitute.org>
8!
9  type foo_t
10    real, allocatable :: bigarr
11  end type
12  block
13    type(foo_t) :: foo
14    allocate(foo%bigarr)
15    call foo_1d (1,[foo]) ! was lost
16    call foo_1d (1,bar_1d()) ! Check that this is OK
17  end block
18contains
19  subroutine foo_1d (n,foo)
20    integer n
21    type(foo_t) :: foo(n)
22  end subroutine
23  function bar_1d () result (array)
24    type(foo_t) :: array(1)
25    allocate (array(1)%bigarr)
26  end function
27end
28! { dg-final { scan-tree-dump-times "builtin_malloc" 4 "original" } }
29! { dg-final { scan-tree-dump-times "builtin_free" 4 "original" } }
30! { dg-final { scan-tree-dump-times "while \\(1\\)" 4 "original" } }
31