2017-12-08 Richard Biener <rguenther@suse.de>
[official-gcc.git] / gcc / testsuite / gfortran.dg / coarray_ptr_comp_1.f08
blobf0b51d5ead19e957245fcd4786db5c715b84167f
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_get_by_ref()-routine.
7 ! Same like coarray_alloc_comp_1 but for pointers.
9 program main
11 implicit none
13 type :: mytype
14   integer :: i
15   integer, pointer :: indices(:)
16   real, dimension(2,5,3) :: volume
17   integer, pointer :: scalar
18   integer :: j
19   integer, pointer :: matrix(:,:)
20   real, pointer :: dynvol(:,:,:)
21 end type
23 type arrtype
24   type(mytype), pointer :: vec(:)
25   type(mytype), pointer :: mat(:,:)
26 end type arrtype
28 type(mytype), save :: object[*]
29 type(arrtype), save :: bar[*]
30 integer :: i,j,me,neighbor
31 integer :: idx(5)
32 real, allocatable :: volume(:,:,:), vol2(:,:,:)
33 real, target :: vol_static(2,5,3)
35 idx = (/ 1,2,1,7,5 /)
37 me=this_image()
38 allocate(object%indices, source=[(i,i=1,5)])
39 allocate(object%scalar, object%matrix(10,7))
40 object%i = 37
41 object%scalar = 42
42 vol_static = reshape([(i, i=1, 2*5*3)], [2, 5, 3])
43 object%volume = vol_static
44 object%matrix = reshape([(i, i=1, 70)], [10, 7])
45 object%dynvol => vol_static
46 sync all
47 neighbor = merge(1,neighbor,me==num_images())
48 if (object[neighbor]%scalar /= 42) call abort()
49 if (object[neighbor]%indices(4) /= 4) call abort()
50 if (object[neighbor]%matrix(3,6) /= 53) call abort()
51 if (any( object[neighbor]%indices(:) /= [1,2,3,4,5] )) call abort()
52 if (any( object[neighbor]%matrix(:,:) /= reshape([(i, i=1, 70)], [10, 7]))) call abort()
53 if (any( object[neighbor]%matrix(3,:) /= [(i * 10 + 3, i=0, 6)])) call abort()
54 if (any( object[neighbor]%matrix(:,2) /= [(i + 10, i=1, 10)])) call abort()
55 if (any( object[neighbor]%matrix(idx,2) /= [11, 12, 11, 17, 15])) call abort()
56 if (any( object[neighbor]%matrix(3,idx) /= [3, 13, 3, 63, 43])) call abort()
57 if (any( object[neighbor]%matrix(2:8:4, 5:1:-1) /= reshape([42, 46, 32, 36, 22, 26, 12, 16, 2, 6], [2,5]))) call abort()
58 if (any( object[neighbor]%matrix(:8:4, 2::2) /= reshape([11, 15, 31, 35, 51, 55], [2,3]))) call abort()
59 if (any( object[neighbor]%volume /= vol_static)) call abort()
60 if (any( object[neighbor]%dynvol /= vol_static)) call abort()
61 if (any( object[neighbor]%volume(:, 2:4, :) /= vol_static(:, 2:4, :))) call abort()
62 if (any( object[neighbor]%dynvol(:, 2:4, :) /= vol_static(:, 2:4, :))) call abort()
64 vol2 = vol_static(:, ::2, :)
65 if (any( object[neighbor]%volume(:, ::2, :) /= vol2)) call abort()
66 if (any( object[neighbor]%dynvol(:, ::2, :) /= vol2)) call abort()
68 allocate(bar%vec(-2:2))
70 bar%vec(1)%volume = vol_static
71 if (any(bar[neighbor]%vec(1)%volume /= vol_static)) call abort()
73 i = 15
74 allocate(bar%vec(1)%scalar, bar%vec(0)%scalar)
75 bar%vec(1)%scalar = i
76 if (.not. associated(bar%vec(1)%scalar)) call abort()
77 if (bar[neighbor]%vec(1)%scalar /= 15) call abort()
79 bar%vec(0)%scalar = 27
80 if (.not. associated(bar%vec(0)%scalar)) call abort()
81 if (bar[neighbor]%vec(0)%scalar /= 27) call abort()
83 allocate(bar%vec(1)%indices(3), bar%vec(2)%indices(5))
84 bar%vec(1)%indices = [ 3, 4, 15 ]
85 bar%vec(2)%indices = 89
87 if (.not. associated(bar%vec(1)%indices)) call abort()
88 if (associated(bar%vec(-2)%indices)) call abort()
89 if (associated(bar%vec(-1)%indices)) call abort()
90 if (associated(bar%vec( 0)%indices)) call abort()
91 if (.not. associated(bar%vec( 2)%indices)) call abort()
92 if (any(bar[me]%vec(2)%indices /= 89)) call abort()
94 if (any (bar[neighbor]%vec(1)%indices /= [ 3,4,15])) call abort()
96 deallocate(bar%vec(2)%indices, bar%vec(1)%indices, bar%vec(1)%scalar, bar%vec(0)%scalar)
97 deallocate(object%indices, object%scalar, object%matrix)
98 deallocate(bar%vec)
99 end program