PR inline-asm/84742
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_allocate_8.f08
blob0e83ec5c46c87169cc0c3c8c9741029dd131f370
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=lib -lcaf_single -fdump-tree-original" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
5 program alloc_comp
6   implicit none
8   type coords
9     real,allocatable :: x(:)
10     real,allocatable :: y(:)
11     real,allocatable :: z(:)
12   end type
14   integer :: me,np,n,i
15   type(coords) :: coo[*]
17   ! with caf_single num_images is always == 1
18   me = this_image(); np = num_images()
19   n = 100
21   allocate(coo%x(n),coo%y(n),coo%z(n))
23   coo%y = me
25   do i=1, n
26         coo%y(i) = coo%y(i) + i
27   end do
29   sync all
31   ! Check the caf_get()-offset is computed correctly.
32   if(me == 1 .and. coo[np]%y(10) /= 11 ) STOP 1
34   ! Check the whole array is correct.
35   if (me == 1 .and. any( coo[np]%y /= [(i, i=2, 101)] ) ) STOP 2
37   deallocate(coo%x)
39 end program