annotate gcc/testsuite/gfortran.dg/coarray_ptr_comp_1.f08 @ 152:2b5abeee2509

update gcc11
author anatofuz
date Mon, 25 May 2020 07:50:57 +0900
parents 84e7813d76e9
children
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
111
kono
parents:
diff changeset
1 ! { dg-do run }
kono
parents:
diff changeset
2 ! { dg-options "-fcoarray=lib -lcaf_single" }
kono
parents:
diff changeset
3 ! { dg-additional-options "-latomic" { target libatomic_available } }
kono
parents:
diff changeset
4
kono
parents:
diff changeset
5 ! Contributed by Damian Rouson
kono
parents:
diff changeset
6 ! Check the new _caf_get_by_ref()-routine.
kono
parents:
diff changeset
7 ! Same like coarray_alloc_comp_1 but for pointers.
kono
parents:
diff changeset
8
kono
parents:
diff changeset
9 program main
kono
parents:
diff changeset
10
kono
parents:
diff changeset
11 implicit none
kono
parents:
diff changeset
12
kono
parents:
diff changeset
13 type :: mytype
kono
parents:
diff changeset
14 integer :: i
kono
parents:
diff changeset
15 integer, pointer :: indices(:)
kono
parents:
diff changeset
16 real, dimension(2,5,3) :: volume
kono
parents:
diff changeset
17 integer, pointer :: scalar
kono
parents:
diff changeset
18 integer :: j
kono
parents:
diff changeset
19 integer, pointer :: matrix(:,:)
kono
parents:
diff changeset
20 real, pointer :: dynvol(:,:,:)
kono
parents:
diff changeset
21 end type
kono
parents:
diff changeset
22
kono
parents:
diff changeset
23 type arrtype
kono
parents:
diff changeset
24 type(mytype), pointer :: vec(:)
kono
parents:
diff changeset
25 type(mytype), pointer :: mat(:,:)
kono
parents:
diff changeset
26 end type arrtype
kono
parents:
diff changeset
27
kono
parents:
diff changeset
28 type(mytype), save :: object[*]
kono
parents:
diff changeset
29 type(arrtype), save :: bar[*]
kono
parents:
diff changeset
30 integer :: i,j,me,neighbor
kono
parents:
diff changeset
31 integer :: idx(5)
kono
parents:
diff changeset
32 real, allocatable :: volume(:,:,:), vol2(:,:,:)
kono
parents:
diff changeset
33 real, target :: vol_static(2,5,3)
kono
parents:
diff changeset
34
kono
parents:
diff changeset
35 idx = (/ 1,2,1,7,5 /)
kono
parents:
diff changeset
36
kono
parents:
diff changeset
37 me=this_image()
kono
parents:
diff changeset
38 allocate(object%indices, source=[(i,i=1,5)])
kono
parents:
diff changeset
39 allocate(object%scalar, object%matrix(10,7))
kono
parents:
diff changeset
40 object%i = 37
kono
parents:
diff changeset
41 object%scalar = 42
kono
parents:
diff changeset
42 vol_static = reshape([(i, i=1, 2*5*3)], [2, 5, 3])
kono
parents:
diff changeset
43 object%volume = vol_static
kono
parents:
diff changeset
44 object%matrix = reshape([(i, i=1, 70)], [10, 7])
kono
parents:
diff changeset
45 object%dynvol => vol_static
kono
parents:
diff changeset
46 sync all
kono
parents:
diff changeset
47 neighbor = merge(1,neighbor,me==num_images())
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
48 if (object[neighbor]%scalar /= 42) STOP 1
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
49 if (object[neighbor]%indices(4) /= 4) STOP 2
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
50 if (object[neighbor]%matrix(3,6) /= 53) STOP 3
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
51 if (any( object[neighbor]%indices(:) /= [1,2,3,4,5] )) STOP 4
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
52 if (any( object[neighbor]%matrix(:,:) /= reshape([(i, i=1, 70)], [10, 7]))) STOP 5
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
53 if (any( object[neighbor]%matrix(3,:) /= [(i * 10 + 3, i=0, 6)])) STOP 6
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
54 if (any( object[neighbor]%matrix(:,2) /= [(i + 10, i=1, 10)])) STOP 7
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
55 if (any( object[neighbor]%matrix(idx,2) /= [11, 12, 11, 17, 15])) STOP 8
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
56 if (any( object[neighbor]%matrix(3,idx) /= [3, 13, 3, 63, 43])) STOP 9
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
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]))) STOP 10
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
58 if (any( object[neighbor]%matrix(:8:4, 2::2) /= reshape([11, 15, 31, 35, 51, 55], [2,3]))) STOP 11
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
59 if (any( object[neighbor]%volume /= vol_static)) STOP 12
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
60 if (any( object[neighbor]%dynvol /= vol_static)) STOP 13
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
61 if (any( object[neighbor]%volume(:, 2:4, :) /= vol_static(:, 2:4, :))) STOP 14
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
62 if (any( object[neighbor]%dynvol(:, 2:4, :) /= vol_static(:, 2:4, :))) STOP 15
111
kono
parents:
diff changeset
63
kono
parents:
diff changeset
64 vol2 = vol_static(:, ::2, :)
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
65 if (any( object[neighbor]%volume(:, ::2, :) /= vol2)) STOP 16
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
66 if (any( object[neighbor]%dynvol(:, ::2, :) /= vol2)) STOP 17
111
kono
parents:
diff changeset
67
kono
parents:
diff changeset
68 allocate(bar%vec(-2:2))
kono
parents:
diff changeset
69
kono
parents:
diff changeset
70 bar%vec(1)%volume = vol_static
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
71 if (any(bar[neighbor]%vec(1)%volume /= vol_static)) STOP 18
111
kono
parents:
diff changeset
72
kono
parents:
diff changeset
73 i = 15
kono
parents:
diff changeset
74 allocate(bar%vec(1)%scalar, bar%vec(0)%scalar)
kono
parents:
diff changeset
75 bar%vec(1)%scalar = i
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
76 if (.not. associated(bar%vec(1)%scalar)) STOP 19
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
77 if (bar[neighbor]%vec(1)%scalar /= 15) STOP 20
111
kono
parents:
diff changeset
78
kono
parents:
diff changeset
79 bar%vec(0)%scalar = 27
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
80 if (.not. associated(bar%vec(0)%scalar)) STOP 21
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
81 if (bar[neighbor]%vec(0)%scalar /= 27) STOP 22
111
kono
parents:
diff changeset
82
kono
parents:
diff changeset
83 allocate(bar%vec(1)%indices(3), bar%vec(2)%indices(5))
kono
parents:
diff changeset
84 bar%vec(1)%indices = [ 3, 4, 15 ]
kono
parents:
diff changeset
85 bar%vec(2)%indices = 89
kono
parents:
diff changeset
86
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
87 if (.not. associated(bar%vec(1)%indices)) STOP 23
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
88 if (associated(bar%vec(-2)%indices)) STOP 24
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
89 if (associated(bar%vec(-1)%indices)) STOP 25
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
90 if (associated(bar%vec( 0)%indices)) STOP 26
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
91 if (.not. associated(bar%vec( 2)%indices)) STOP 27
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
92 if (any(bar[me]%vec(2)%indices /= 89)) STOP 28
111
kono
parents:
diff changeset
93
131
84e7813d76e9 gcc-8.2
mir3636
parents: 111
diff changeset
94 if (any (bar[neighbor]%vec(1)%indices /= [ 3,4,15])) STOP 29
111
kono
parents:
diff changeset
95
kono
parents:
diff changeset
96 deallocate(bar%vec(2)%indices, bar%vec(1)%indices, bar%vec(1)%scalar, bar%vec(0)%scalar)
kono
parents:
diff changeset
97 deallocate(object%indices, object%scalar, object%matrix)
kono
parents:
diff changeset
98 deallocate(bar%vec)
kono
parents:
diff changeset
99 end program