[libc++] Add test_demangle.pass.cpp clang-format to .git-blame-ignore-revs
[llvm-project.git] / flang / test / Semantics / OpenACC / acc-parallel.f90
blob3f17d8fc862a67894ce875c77f9c69b12086de6d
1 ! RUN: %python %S/../test_errors.py %s %flang -fopenacc
3 ! Check OpenACC clause validity for the following construct and directive:
4 ! 2.5.1 Parallel
6 program openacc_parallel_validity
8 implicit none
10 integer :: i, j, b, gang_size, vector_size, worker_size
11 integer, parameter :: N = 256
12 integer, dimension(N) :: c
13 logical, dimension(N) :: d, e
14 integer :: async1
15 integer :: wait1, wait2
16 real :: reduction_r
17 logical :: reduction_l
18 real(8), dimension(N, N) :: aa, bb, cc
19 real(8), dimension(:), allocatable :: dd
20 real(8), pointer :: p
21 logical :: ifCondition = .TRUE.
22 real(8), dimension(N) :: a, f, g, h
24 !$acc parallel device_type(*) num_gangs(2)
25 !$acc loop
26 do i = 1, N
27 a(i) = 3.14
28 end do
29 !$acc end parallel
31 !$acc parallel async
32 !$acc end parallel
34 !$acc parallel async(1)
35 !$acc end parallel
37 !$acc parallel async(async1)
38 !$acc end parallel
40 !$acc parallel wait
41 !$acc end parallel
43 !$acc parallel wait(1)
44 !$acc end parallel
46 !$acc parallel wait(wait1)
47 !$acc end parallel
49 !$acc parallel wait(1,2)
50 !$acc end parallel
52 !$acc parallel wait(wait1, wait2)
53 !$acc end parallel
55 !$acc parallel num_gangs(8)
56 !$acc end parallel
58 !ERROR: NUM_GANGS clause accepts a maximum of 3 arguments
59 !$acc parallel num_gangs(1, 1, 1, 1)
60 !$acc end parallel
62 !$acc parallel num_workers(8)
63 !$acc end parallel
65 !$acc parallel vector_length(128)
66 !$acc end parallel
68 !$acc parallel if(.true.)
69 !$acc end parallel
71 !$acc parallel if(ifCondition)
72 !$acc end parallel
74 !$acc parallel self
75 !$acc end parallel
77 !$acc parallel self(.true.)
78 !$acc end parallel
80 !$acc parallel self(ifCondition)
81 !$acc end parallel
83 !$acc parallel copy(aa) copyin(bb) copyout(cc)
84 !$acc end parallel
86 !$acc parallel copy(aa, bb) copyout(zero: cc)
87 !$acc end parallel
89 !$acc parallel present(aa, bb) create(cc)
90 !$acc end parallel
92 !$acc parallel copyin(readonly: aa, bb) create(zero: cc)
93 !$acc end parallel
95 !$acc parallel deviceptr(aa, bb) no_create(cc)
96 !$acc end parallel
98 !ERROR: Argument `cc` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
99 !$acc parallel attach(dd, p, cc)
100 !$acc end parallel
102 !$acc parallel private(aa) firstprivate(bb, cc)
103 !$acc end parallel
105 !$acc parallel default(none)
106 !$acc end parallel
108 !$acc parallel default(present)
109 !$acc end parallel
111 !$acc parallel device_type(*)
112 !$acc end parallel
114 !$acc parallel device_type(default)
115 !$acc end parallel
117 !$acc parallel device_type(default, host)
118 !$acc end parallel
120 !ERROR: Clause PRIVATE is not allowed after clause DEVICE_TYPE on the PARALLEL directive
121 !ERROR: Clause FIRSTPRIVATE is not allowed after clause DEVICE_TYPE on the PARALLEL directive
122 !$acc parallel device_type(*) private(aa) firstprivate(bb)
123 !$acc end parallel
125 !$acc parallel device_type(*) async
126 !$acc end parallel
128 !$acc parallel device_type(*) wait
129 !$acc end parallel
131 !$acc parallel device_type(*) num_gangs(8)
132 !$acc end parallel
134 !$acc parallel device_type(*) async device_type(host) wait
135 !$acc end parallel
137 !ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the PARALLEL directive
138 !$acc parallel device_type(*) if(.TRUE.)
139 !$acc loop
140 do i = 1, N
141 a(i) = 3.14
142 end do
143 !$acc end parallel
145 do i = 1, 100
146 !$acc parallel
147 !ERROR: CYCLE to construct outside of PARALLEL construct is not allowed
148 if (i == 10) cycle
149 !$acc end parallel
150 end do
152 !$acc parallel
153 do i = 1, 100
154 if (i == 10) cycle
155 end do
156 !$acc end parallel
158 !ERROR: At most one NUM_GANGS clause can appear on the PARALLEL directive or in group separated by the DEVICE_TYPE clause
159 !$acc parallel num_gangs(400) num_gangs(400)
160 !$acc end parallel
162 !ERROR: At most one NUM_GANGS clause can appear on the PARALLEL directive or in group separated by the DEVICE_TYPE clause
163 !$acc parallel device_type(nvidia) num_gangs(400) num_gangs(200)
164 !$acc end parallel
166 !$acc parallel device_type(nvidia) num_gangs(400) device_type(radeon) num_gangs(200)
167 !$acc end parallel
169 !ERROR: At most one NUM_WORKERS clause can appear on the PARALLEL directive or in group separated by the DEVICE_TYPE clause
170 !$acc parallel num_workers(8) num_workers(4)
171 !$acc end parallel
173 !ERROR: At most one NUM_WORKERS clause can appear on the PARALLEL directive or in group separated by the DEVICE_TYPE clause
174 !$acc parallel device_type(nvidia) num_workers(8) num_workers(4)
175 !$acc end parallel
177 !$acc parallel device_type(nvidia) num_workers(8) device_type(radeon) num_workers(4)
178 !$acc end parallel
180 !ERROR: At most one VECTOR_LENGTH clause can appear on the PARALLEL directive or in group separated by the DEVICE_TYPE clause
181 !$acc parallel vector_length(128) vector_length(124)
182 !$acc end parallel
184 !ERROR: At most one VECTOR_LENGTH clause can appear on the PARALLEL directive or in group separated by the DEVICE_TYPE clause
185 !$acc parallel device_type(nvidia) vector_length(256) vector_length(128)
186 !$acc end parallel
188 !$acc parallel device_type(nvidia) vector_length(256) device_type(radeon) vector_length(128)
189 !$acc end parallel
191 end program openacc_parallel_validity