2 ! { dg-options "-fcoarray=lib -lcaf_single -fdump-tree-original" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
9 real,allocatable :: x(:)
10 real,allocatable :: y(:)
11 real,allocatable :: z(:)
15 type(coords) :: coo[*]
17 ! with caf_single num_images is always == 1
18 me = this_image(); np = num_images()
21 allocate(coo%x(n),coo%y(n),coo%z(n))
26 coo%y(i) = coo%y(i) + i
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