[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / OpenACC / acc-data.f90
blob6aa99e71e0bb9e783afa0bf3ab49b9d0c07212f5
1 ! RUN: %S/../test_errors.sh %s %t %flang -fopenacc
2 ! REQUIRES: shell
4 ! Check OpenACC clause validity for the following construct and directive:
5 ! 2.6.5 Data
6 ! 2.14.6 Enter Data
7 ! 2.14.7 Exit Data
9 program openacc_data_validity
11 implicit none
13 type atype
14 real(8), dimension(10) :: arr
15 real(8) :: s
16 end type atype
18 integer :: i, j, b, gang_size, vector_size, worker_size
19 integer, parameter :: N = 256
20 integer, dimension(N) :: c
21 logical, dimension(N) :: d, e
22 integer :: async1
23 integer :: wait1, wait2
24 real :: reduction_r
25 logical :: reduction_l
26 real(8), dimension(N, N) :: aa, bb, cc
27 real(8), dimension(:), allocatable :: dd
28 real(8), pointer :: p
29 logical :: ifCondition = .TRUE.
30 type(atype) :: t
31 type(atype), dimension(10) :: ta
33 real(8), dimension(N) :: a, f, g, h
35 !ERROR: At least one of ATTACH, COPYIN, CREATE clause must appear on the ENTER DATA directive
36 !$acc enter data
38 !ERROR: Modifier is not allowed for the COPYIN clause on the ENTER DATA directive
39 !$acc enter data copyin(zero: i)
41 !ERROR: Only the ZERO modifier is allowed for the CREATE clause on the ENTER DATA directive
42 !$acc enter data create(readonly: i)
44 !ERROR: COPYOUT clause is not allowed on the ENTER DATA directive
45 !$acc enter data copyin(i) copyout(i)
47 !$acc enter data create(aa) if(.TRUE.)
49 !ERROR: At most one IF clause can appear on the ENTER DATA directive
50 !$acc enter data create(aa) if(.TRUE.) if(ifCondition)
52 !$acc enter data create(aa) if(ifCondition)
54 !$acc enter data create(aa) async
56 !ERROR: At most one ASYNC clause can appear on the ENTER DATA directive
57 !$acc enter data create(aa) async async
59 !$acc enter data create(aa) async(async1)
61 !$acc enter data create(aa) async(1)
63 !$acc enter data create(aa) wait(1)
65 !$acc enter data create(aa) wait(wait1)
67 !$acc enter data create(aa) wait(wait1, wait2)
69 !$acc enter data create(aa) wait(wait1) wait(wait2)
71 !ERROR: Argument `bb` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
72 !$acc enter data attach(bb)
74 !ERROR: At least one of COPYOUT, DELETE, DETACH clause must appear on the EXIT DATA directive
75 !$acc exit data
77 !ERROR: Modifier is not allowed for the COPYOUT clause on the EXIT DATA directive
78 !$acc exit data copyout(zero: i)
80 !$acc exit data delete(aa)
82 !$acc exit data delete(aa) finalize
84 !ERROR: At most one FINALIZE clause can appear on the EXIT DATA directive
85 !$acc exit data delete(aa) finalize finalize
87 !ERROR: Argument `cc` on the DETACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
88 !$acc exit data detach(cc)
90 !ERROR: Argument on the DETACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
91 !$acc exit data detach(/i/)
93 !$acc exit data copyout(bb)
95 !$acc exit data delete(aa) if(.TRUE.)
97 !$acc exit data delete(aa) if(ifCondition)
99 !ERROR: At most one IF clause can appear on the EXIT DATA directive
100 !$acc exit data delete(aa) if(ifCondition) if(.TRUE.)
102 !$acc exit data delete(aa) async
104 !ERROR: At most one ASYNC clause can appear on the EXIT DATA directive
105 !$acc exit data delete(aa) async async
107 !$acc exit data delete(aa) async(async1)
109 !$acc exit data delete(aa) async(1)
111 !$acc exit data delete(aa) wait(1)
113 !$acc exit data delete(aa) wait(wait1)
115 !$acc exit data delete(aa) wait(wait1, wait2)
117 !$acc exit data delete(aa) wait(wait1) wait(wait2)
119 !ERROR: Only the ZERO modifier is allowed for the COPYOUT clause on the DATA directive
120 !$acc data copyout(readonly: i)
121 !$acc end data
123 !ERROR: At most one IF clause can appear on the DATA directive
124 !$acc data copy(i) if(.true.) if(.true.)
125 !$acc end data
127 !ERROR: At least one of COPYOUT, DELETE, DETACH clause must appear on the EXIT DATA directive
128 !$acc exit data
130 !ERROR: At least one of ATTACH, COPY, COPYIN, COPYOUT, CREATE, DEFAULT, DEVICEPTR, NO_CREATE, PRESENT clause must appear on the DATA directive
131 !$acc data
132 !$acc end data
134 !$acc data copy(aa) if(.true.)
135 !$acc end data
137 !$acc data copy(aa) if(ifCondition)
138 !$acc end data
140 !$acc data copy(aa, bb, cc)
141 !$acc end data
143 !$acc data copyin(aa) copyin(readonly: bb) copyout(cc)
144 !$acc end data
146 !$acc data copyin(readonly: aa, bb) copyout(zero: cc)
147 !$acc end data
149 !$acc data create(aa, bb(:,:)) create(zero: cc(:,:))
150 !$acc end data
152 !$acc data no_create(aa) present(bb, cc)
153 !$acc end data
155 !$acc data deviceptr(aa) attach(dd, p)
156 !$acc end data
158 !$acc data copy(aa, bb) default(none)
159 !$acc end data
161 !$acc data copy(aa, bb) default(present)
162 !$acc end data
164 !ERROR: At most one DEFAULT clause can appear on the DATA directive
165 !$acc data copy(aa, bb) default(none) default(present)
166 !$acc end data
168 !ERROR: At most one IF clause can appear on the DATA directive
169 !$acc data copy(aa) if(.true.) if(ifCondition)
170 !$acc end data
172 !$acc data copyin(i)
173 !ERROR: Unmatched PARALLEL directive
174 !$acc end parallel
176 end program openacc_data_validity