aarch64: Add missing ACLE macro for NEON-SVE Bridge
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_allocate_7.f08
blob5a72438e86223cf318d935f9f0ab0a92ab1b9cb3
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=lib -lcaf_single -fdump-tree-original" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
5 ! Contributed by Damian Rouson
6 ! Checking whether (de-)registering of coarrays works.
8 program main
10   implicit none
12   type mytype
13     integer, allocatable :: indices(:)
14   end type
16   type(mytype), save :: object[*]
17   integer :: i,me
19   me=this_image() ! me is always 1 here
20   object%indices=[(i,i=1,me)]
21   if ( size(object%indices) /= 1 ) STOP 1
22   ! therefore no array is present here and no array test needed.
23   if ( object%indices(1) /= 1 ) STOP 2
24 end program
26 ! { dg-final { scan-tree-dump-times "_gfortran_caf_register \\(D.\[0-9\]+, 1, &\\(\\(struct mytype\\) \\*object\\).indices.token, &\\(\\(struct mytype\\) \\*object\\).indices, 0B, 0B, 0\\);" 1 "original" } }
27 ! { dg-final { scan-tree-dump-times "_gfortran_caf_register \\(D.\[0-9\]+, 8, &\\(\\(struct mytype\\) \\*object\\).indices.token, &\\(\\(struct mytype\\) \\*object\\).indices, 0B, 0B, 0\\);" 1 "original" } }
28 ! { dg-final { scan-tree-dump-times "_gfortran_caf_deregister \\(&\\(\\(struct mytype\\) \\*object\\).indices.token, 1, 0B, 0B, 0\\);" 1 "original" } }