c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_atomic_6.f90
bloba0f19a84eff05f114f7114da8add2e42a0f5e28b
1 ! { dg-do compile }
2 ! { dg-options "-fcoarray=single" }
4 ! Contributed by Reinhold Bader
7 program def_and_ref
8 ! compile only
9 use, intrinsic :: iso_fortran_env
10 implicit none
11 type :: e
12 integer(kind=atomic_int_kind) :: ia = 0
13 logical(kind=atomic_logical_kind) :: la = .false.
14 end type
16 type(e) :: a[*]
18 integer :: ival = 0
19 logical :: lval = .false.
21 if (this_image() == 1) then
22 call atomic_define(a[num_images()]%ia, 4)
23 call atomic_define(a[num_images()]%la, .true.)
24 end if
25 if (this_image() == num_images()) then
26 do while (ival == 0 .or. .not. lval)
27 call atomic_ref(ival, a%ia)
28 call atomic_ref(lval, a%la)
29 end do
30 if (ival == 4 .and. lval) then
31 write(*,*) 'OK'
32 else
33 write(*,*) 'FAIL: ival,lval =', ival, lval
34 end if
35 end if
36 end program