c: Fix up pointer types to may_alias structures [PR114493]
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_alloc_comp_2.f08
blobb07d882196eb8725365dc1516e1ec3975a62015f
1 ! { dg-do run }
2 ! { dg-options "-fcoarray=lib -lcaf_single" }
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
5 ! Contributed by Damian Rouson
6 ! Check the new _caf_send_by_ref()-routine.
8 program main
10 implicit none
12 type :: mytype
13   integer :: i
14   integer, allocatable :: indices(:)
15   real, dimension(2,5,3) :: volume
16   integer, allocatable :: scalar
17   integer :: j
18   integer, allocatable :: matrix(:,:)
19   real, allocatable :: dynvol(:,:,:)
20 end type
22 type arrtype
23   type(mytype), allocatable :: vec(:)
24   type(mytype), allocatable :: mat(:,:)
25 end type arrtype
27 type(mytype), save :: object[*]
28 type(arrtype), save :: bar[*]
29 integer :: i,j,me,neighbor
30 integer :: idx(5)
31 real, allocatable :: volume(:,:,:), vol2(:,:,:)
32 real :: vol_static(2,5,3)
34 idx = (/ 1,2,1,7,5 /)
36 me=this_image()
37 neighbor = merge(1,me+1,me==num_images())
38 object[neighbor]%indices=[(i,i=1,5)]
39 object[neighbor]%i = 37
40 object[neighbor]%scalar = 42
41 vol_static = reshape([(i, i=1, 2*5*3)], [2, 5, 3])
42 object[neighbor]%volume = vol_static
43 object[neighbor]%matrix = reshape([(i, i=1, 70)], [10, 7])
44 object[neighbor]%dynvol = vol_static
45 sync all
46 if (object%scalar /= 42) STOP 1
47 if (any( object%indices /= [1,2,3,4,5] )) STOP 2
48 if (any( object%matrix /= reshape([(i, i=1, 70)], [10, 7]))) STOP 3
49 if (any( object%volume /= vol_static)) STOP 4
50 if (any( object%dynvol /= vol_static)) STOP 5
52 vol2 = vol_static
53 vol2(:, ::2, :) = 42
54 object[neighbor]%volume(:, ::2, :) = 42
55 object[neighbor]%dynvol(:, ::2, :) = 42
56 if (any( object%volume /= vol2)) STOP 6
57 if (any( object%dynvol /= vol2)) STOP 7
59 allocate(bar%vec(-2:2))
61 bar[neighbor]%vec(1)%volume = vol_static
62 if (any(bar%vec(1)%volume /= vol_static)) STOP 8
64 i = 15
65 bar[neighbor]%vec(1)%scalar = i
66 if (.not. allocated(bar%vec(1)%scalar)) STOP 9
67 if (bar%vec(1)%scalar /= 15) STOP 10
69 bar[neighbor]%vec(0)%scalar = 27
70 if (.not. allocated(bar%vec(0)%scalar)) STOP 11
71 if (bar%vec(0)%scalar /= 27) STOP 12
73 bar[neighbor]%vec(1)%indices = [ 3, 4, 15 ]
74 allocate(bar%vec(2)%indices(5))
75 bar[neighbor]%vec(2)%indices = 89
77 if (.not. allocated(bar%vec(1)%indices)) STOP 13
78 if (allocated(bar%vec(-2)%indices)) STOP 14
79 if (allocated(bar%vec(-1)%indices)) STOP 15
80 if (allocated(bar%vec( 0)%indices)) STOP 16
81 if (.not. allocated(bar%vec( 2)%indices)) STOP 17
82 if (any(bar%vec(2)%indices /= 89)) STOP 18
84 if (any (bar%vec(1)%indices /= [ 3,4,15])) STOP 19
85 end program