[C++ PATCH] Deprecate -ffriend-injection
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_allocate_10.f08
blob89e7bb4a9812bf2146a919d9a23de4cfc508a235
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=lib -lcaf_single" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
5 program alloc_comp
6   implicit none
8   type coords
9     integer,allocatable :: x(:)
10   end type
12   type outerT
13     type(coords),allocatable :: coo[:]
14   end type
15   integer :: me,np,n,i
16   type(outerT) :: o
18   ! with caf_single num_images is always == 1
19   me = this_image(); np = num_images()
20   n = 100
22   allocate(o%coo[*])
23   allocate(o%coo%x(n))
25   o%coo%x = me
27   do i=1, n
28         o%coo%x(i) = o%coo%x(i) + i
29   end do
31   sync all
33   if(me == 1 .and. o%coo[np]%x(10) /= 11 ) call abort()
35   ! Check the whole array is correct.
36   if (me == 1 .and. any( o%coo[np]%x /= [(i, i=2, 101)] ) ) call abort()
38   deallocate(o%coo%x)
40 end program