2017-02-20 Paul Thomas <pault@gcc.gnu.org>
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_alloc_with_implicit_sync_2.f90
blobeccfde37f82266a3e6413f1b1c5dda666e0c198a
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=lib -fdump-tree-original" }
3 !
4 ! Test that the compiler generates sync_all statements only at the required
5 ! locations. This program is not supposed to run (allocating already alloced).
7 program test_alloc_sync
9 type :: T
10 integer, allocatable :: i
11 end type T
12 type :: T2
13 type(T), allocatable :: o[:]
14 end type T2
16 integer, allocatable :: caf[:]
17 type (T) :: obj[*]
18 type (T2) :: cafcomp
20 allocate(caf[*]) ! implicit sync_all
21 allocate(obj%i) ! asynchronous
22 allocate(cafcomp%o[*]) ! sync
23 allocate(cafcomp%o%i) ! async
25 allocate(obj%i, cafcomp%o%i) ! async
26 allocate(caf[*], obj%i, cafcomp%o%i) ! sync
28 end program test_alloc_sync
30 ! { dg-final { scan-tree-dump-times "caf_sync_all" 3 "original" } }