[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / OpenACC / acc-parallel.f90
blob75fb14fccc229410339010e280305130dea8338d
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.5.1 Parallel
7 program openacc_parallel_validity
9 implicit none
11 integer :: i, j, b, gang_size, vector_size, worker_size
12 integer, parameter :: N = 256
13 integer, dimension(N) :: c
14 logical, dimension(N) :: d, e
15 integer :: async1
16 integer :: wait1, wait2
17 real :: reduction_r
18 logical :: reduction_l
19 real(8), dimension(N, N) :: aa, bb, cc
20 real(8), dimension(:), allocatable :: dd
21 real(8), pointer :: p
22 logical :: ifCondition = .TRUE.
23 real(8), dimension(N) :: a, f, g, h
25 !$acc parallel device_type(*) num_gangs(2)
26 !$acc loop
27 do i = 1, N
28 a(i) = 3.14
29 end do
30 !$acc end parallel
32 !$acc parallel async
33 !$acc end parallel
35 !$acc parallel async(1)
36 !$acc end parallel
38 !$acc parallel async(async1)
39 !$acc end parallel
41 !$acc parallel wait
42 !$acc end parallel
44 !$acc parallel wait(1)
45 !$acc end parallel
47 !$acc parallel wait(wait1)
48 !$acc end parallel
50 !$acc parallel wait(1,2)
51 !$acc end parallel
53 !$acc parallel wait(wait1, wait2)
54 !$acc end parallel
56 !$acc parallel num_gangs(8)
57 !$acc end parallel
59 !$acc parallel num_workers(8)
60 !$acc end parallel
62 !$acc parallel vector_length(128)
63 !$acc end parallel
65 !$acc parallel if(.true.)
66 !$acc end parallel
68 !$acc parallel if(ifCondition)
69 !$acc end parallel
71 !$acc parallel self
72 !$acc end parallel
74 !$acc parallel self(.true.)
75 !$acc end parallel
77 !$acc parallel self(ifCondition)
78 !$acc end parallel
80 !$acc parallel copy(aa) copyin(bb) copyout(cc)
81 !$acc end parallel
83 !$acc parallel copy(aa, bb) copyout(zero: cc)
84 !$acc end parallel
86 !$acc parallel present(aa, bb) create(cc)
87 !$acc end parallel
89 !$acc parallel copyin(readonly: aa, bb) create(zero: cc)
90 !$acc end parallel
92 !$acc parallel deviceptr(aa, bb) no_create(cc)
93 !$acc end parallel
95 !ERROR: Argument `cc` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
96 !$acc parallel attach(dd, p, cc)
97 !$acc end parallel
99 !$acc parallel private(aa) firstprivate(bb, cc)
100 !$acc end parallel
102 !$acc parallel default(none)
103 !$acc end parallel
105 !$acc parallel default(present)
106 !$acc end parallel
108 !$acc parallel device_type(*)
109 !$acc end parallel
111 !$acc parallel device_type(1)
112 !$acc end parallel
114 !$acc parallel device_type(1, 3)
115 !$acc end parallel
117 !ERROR: Clause PRIVATE is not allowed after clause DEVICE_TYPE on the PARALLEL directive
118 !ERROR: Clause FIRSTPRIVATE is not allowed after clause DEVICE_TYPE on the PARALLEL directive
119 !$acc parallel device_type(*) private(aa) firstprivate(bb)
120 !$acc end parallel
122 !$acc parallel device_type(*) async
123 !$acc end parallel
125 !$acc parallel device_type(*) wait
126 !$acc end parallel
128 !$acc parallel device_type(*) num_gangs(8)
129 !$acc end parallel
131 !$acc parallel device_type(1) async device_type(2) wait
132 !$acc end parallel
134 !ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the PARALLEL directive
135 !$acc parallel device_type(*) if(.TRUE.)
136 !$acc loop
137 do i = 1, N
138 a(i) = 3.14
139 end do
140 !$acc end parallel
142 end program openacc_parallel_validity