2 ! { dg-options "-fdump-tree-original" }
6 ! Contributed by G. Steinmetz
9 subroutine sub(x
) bind(c
)
10 implicit none (type, external)
11 integer, allocatable
, intent(out
) :: x(:)
19 implicit none (type, external)
21 subroutine sub(x
) bind(c
)
22 integer, allocatable
, intent(out
) :: x(:)
25 integer, allocatable
:: a(:)
28 if (.not
.allocated(a
)) stop 1
29 if (any(shape(a
) /= [3])) stop 2
30 if (lbound(a
,1) /= 3 .or
. ubound(a
,1) /= 5) stop 3
31 print *, a(0), a(1), a(2), a(3), a(4)
33 if (any(a
/= [1, 2, 3])) stop 4
36 ! "cfi" only appears in context of "a" -> bind-C descriptor
37 ! the intent(out) implies freeing in the callee (!) (when implemented in Fortran), hence the "free"
38 ! and also in the caller (when implemented in Fortran)
39 ! It is the only 'free' as 'a' is part of the main program and, hence, implicitly has the SAVE attribute.
40 ! The 'cfi = 0' appears before the call due to the deallocate and when preparing the C descriptor
41 ! As cfi (i.e. the descriptor itself) is allocated in libgomp, it has to be freed after the call.
43 ! { dg-final { scan-tree-dump-times "__builtin_free" 2 "original" } }
44 ! { dg-final { scan-tree-dump-times "__builtin_free \\(_x->base_addr\\);" 1 "original" } }
45 ! { dg-final { scan-tree-dump-times "_x->base_addr = 0B;" 1 "original" } }
46 ! { dg-final { scan-tree-dump-times "__builtin_free \\(cfi\\.\[0-9\]+\\.base_addr\\);" 1 "original" } }
47 ! { dg-final { scan-tree-dump-times "cfi\\.\[0-9\]+\\.base_addr = 0B;" 1 "original" } }