xref: /llvm-project/flang/test/Semantics/OpenACC/acc-data.f90 (revision a6c02edd6eac476523b5c73f29619a7a9e054872)
1! RUN: %python %S/../test_errors.py %s %flang -fopenacc -pedantic
2
3! Check OpenACC clause validity for the following construct and directive:
4!   2.6.5 Data
5!   2.14.6 Enter Data
6!   2.14.7 Exit Data
7
8program openacc_data_validity
9
10  implicit none
11
12  type atype
13    real(8), dimension(10) :: arr
14    real(8) :: s
15  end type atype
16
17  integer :: i, j, b, gang_size, vector_size, worker_size
18  integer, parameter :: N = 256
19  integer, dimension(N) :: c
20  logical, dimension(N) :: d, e
21  integer :: async1
22  integer :: wait1, wait2
23  real :: reduction_r
24  logical :: reduction_l
25  real(8), dimension(N, N) :: aa, bb, cc
26  real(8), dimension(:), allocatable :: dd
27  real(8), pointer :: p
28  logical :: ifCondition = .TRUE.
29  type(atype) :: t
30  type(atype), dimension(10) :: ta
31
32  real(8), dimension(N) :: a, f, g, h
33
34  !ERROR: At least one of ATTACH, COPYIN, CREATE clause must appear on the ENTER DATA directive
35  !$acc enter data
36
37  !ERROR: Modifier is not allowed for the COPYIN clause on the ENTER DATA directive
38  !$acc enter data copyin(zero: i)
39
40  !ERROR: Only the ZERO modifier is allowed for the CREATE clause on the ENTER DATA directive
41  !$acc enter data create(readonly: i)
42
43  !ERROR: COPYOUT clause is not allowed on the ENTER DATA directive
44  !$acc enter data copyin(i) copyout(i)
45
46  !$acc enter data create(aa) if(.TRUE.)
47
48  !$acc enter data create(a(1:10))
49
50  !$acc enter data create(t%arr)
51
52  !$acc enter data create(t%arr(2:4))
53
54  !ERROR: At most one IF clause can appear on the ENTER DATA directive
55  !$acc enter data create(aa) if(.TRUE.) if(ifCondition)
56
57  !$acc enter data create(aa) if(ifCondition)
58
59  !$acc enter data create(aa) async
60
61  !ERROR: At most one ASYNC clause can appear on the ENTER DATA directive
62  !$acc enter data create(aa) async async
63
64  !$acc enter data create(aa) async(async1)
65
66  !$acc enter data create(aa) async(1)
67
68  !$acc enter data create(aa) wait(1)
69
70  !$acc enter data create(aa) wait(wait1)
71
72  !$acc enter data create(aa) wait(wait1, wait2)
73
74  !$acc enter data create(aa) wait(wait1) wait(wait2)
75
76  !ERROR: Argument `bb` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
77  !$acc enter data attach(bb)
78
79  !ERROR: At least one of COPYOUT, DELETE, DETACH clause must appear on the EXIT DATA directive
80  !$acc exit data
81
82  !ERROR: Modifier is not allowed for the COPYOUT clause on the EXIT DATA directive
83  !$acc exit data copyout(zero: i)
84
85  !$acc exit data delete(aa)
86
87  !$acc exit data delete(aa) finalize
88
89  !ERROR: At most one FINALIZE clause can appear on the EXIT DATA directive
90  !$acc exit data delete(aa) finalize finalize
91
92  !ERROR: Argument `cc` on the DETACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
93  !$acc exit data detach(cc)
94
95  !ERROR: Argument on the DETACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
96  !$acc exit data detach(/i/)
97
98  !$acc exit data copyout(bb)
99
100  !$acc exit data delete(aa) if(.TRUE.)
101
102  !$acc exit data delete(aa) if(ifCondition)
103
104  !ERROR: At most one IF clause can appear on the EXIT DATA directive
105  !$acc exit data delete(aa) if(ifCondition) if(.TRUE.)
106
107  !$acc exit data delete(aa) async
108
109  !ERROR: At most one ASYNC clause can appear on the EXIT DATA directive
110  !$acc exit data delete(aa) async async
111
112  !$acc exit data delete(aa) async(async1)
113
114  !$acc exit data delete(aa) async(1)
115
116  !$acc exit data delete(aa) wait(1)
117
118  !$acc exit data delete(aa) wait(wait1)
119
120  !$acc exit data delete(aa) wait(wait1, wait2)
121
122  !$acc exit data delete(aa) wait(wait1) wait(wait2)
123
124  !ERROR: Only the ZERO modifier is allowed for the COPYOUT clause on the DATA directive
125  !$acc data copyout(readonly: i)
126  !$acc end data
127
128  !ERROR: At most one IF clause can appear on the DATA directive
129  !$acc data copy(i) if(.true.) if(.true.)
130  !$acc end data
131
132  !ERROR: At least one of COPYOUT, DELETE, DETACH clause must appear on the EXIT DATA directive
133  !$acc exit data
134
135  !PORTABILITY: At least one of ATTACH, COPY, COPYIN, COPYOUT, CREATE, DEFAULT, DEVICEPTR, NO_CREATE, PRESENT clause should appear on the DATA directive
136  !$acc data
137  !$acc end data
138
139  !$acc data copy(aa) if(.true.)
140  !$acc end data
141
142  !$acc data copy(aa) if(ifCondition)
143  !$acc end data
144
145  !$acc data copy(aa, bb, cc)
146  !$acc end data
147
148  !$acc data copyin(aa) copyin(readonly: bb) copyout(cc)
149  !$acc end data
150
151  !$acc data copyin(readonly: aa, bb) copyout(zero: cc)
152  !$acc end data
153
154  !$acc data create(aa, bb(:,:)) create(zero: cc(:,:))
155  !$acc end data
156
157  !$acc data no_create(aa) present(bb, cc)
158  !$acc end data
159
160  !$acc data deviceptr(aa) attach(dd, p)
161  !$acc end data
162
163  !$acc data copy(aa, bb) default(none)
164  !$acc end data
165
166  !$acc data copy(aa, bb) default(present)
167  !$acc end data
168
169  !ERROR: At most one DEFAULT clause can appear on the DATA directive
170  !$acc data copy(aa, bb) default(none) default(present)
171  !$acc end data
172
173  !ERROR: At most one IF clause can appear on the DATA directive
174  !$acc data copy(aa) if(.true.) if(ifCondition)
175  !$acc end data
176
177  !$acc data copyin(i)
178  !ERROR: Unmatched PARALLEL directive
179  !$acc end parallel
180
181  !$acc data copy(aa) async
182  !$acc end data
183
184  !$acc data copy(aa) wait
185  !$acc end data
186
187  !$acc data copy(aa) device_type(default) wait
188  !$acc end data
189
190  do i = 1, 100
191    !$acc data copy(aa)
192    !ERROR: CYCLE to construct outside of DATA construct is not allowed
193    if (i == 10) cycle
194    !$acc end data
195  end do
196
197  !$acc data copy(aa)
198  do i = 1, 100
199    if (i == 10) cycle
200  end do
201  !$acc end data
202
203end program openacc_data_validity
204
205module mod1
206  type :: t1
207    integer :: a
208  contains
209    procedure :: t1_proc
210  end type
211
212contains
213
214
215  subroutine t1_proc(this)
216    class(t1) :: this
217  end subroutine
218
219  subroutine sub4(t)
220    type(t1) :: t
221
222    !ERROR: Only variables are allowed in data clauses on the DATA directive
223    !$acc data copy(t%t1_proc)
224    !$acc end data
225  end subroutine
226
227  subroutine sub5()
228    integer, parameter :: iparam = 1024
229    !$acc data copyin(iparam)
230    !$acc end data
231  end subroutine
232end module
233