coarray_41.f90: Add "-latomic" option if libatomic_available.
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray / lib_realloc_1.f90
blobf3d7f35f271e9425185d2df9d8ae6346cc4d899f
1 ! { dg-do run }
3 ! Test that for CAF components _gfortran_caf_deregister is called
4 ! Test that norealloc happens for CAF components during assignment
6 module m
7 type t
8 integer, allocatable :: CAF[:]
9 end type t
10 end module m
12 program main
13 use m
14 type(t), target :: x,y
15 integer, pointer :: ptr
16 allocate(x%caf[*], y%caf[*])
17 ptr => y%caf
18 ptr = 6
19 if (.not.allocated(x%caf)) call abort()
20 if (.not.allocated(y%caf)) call abort()
21 if (y%caf /= 6) call abort ()
22 x = y
23 if (x%caf /= 6) call abort ()
24 if (.not. associated (ptr,y%caf)) call abort()
25 if (associated (ptr,x%caf)) call abort()
26 ptr = 123
27 if (y%caf /= 123) call abort ()
28 if (x%caf /= 6) call abort ()
29 end program main