[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Semantics / OpenACC / acc-parallel.f90
blob758e1a53c0d57b2e31c88ff1d2f1640a10a7e71a
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 !$acc parallel num_workers(8)
59 !$acc end parallel
61 !$acc parallel vector_length(128)
62 !$acc end parallel
64 !$acc parallel if(.true.)
65 !$acc end parallel
67 !$acc parallel if(ifCondition)
68 !$acc end parallel
70 !$acc parallel self
71 !$acc end parallel
73 !$acc parallel self(.true.)
74 !$acc end parallel
76 !$acc parallel self(ifCondition)
77 !$acc end parallel
79 !$acc parallel copy(aa) copyin(bb) copyout(cc)
80 !$acc end parallel
82 !$acc parallel copy(aa, bb) copyout(zero: cc)
83 !$acc end parallel
85 !$acc parallel present(aa, bb) create(cc)
86 !$acc end parallel
88 !$acc parallel copyin(readonly: aa, bb) create(zero: cc)
89 !$acc end parallel
91 !$acc parallel deviceptr(aa, bb) no_create(cc)
92 !$acc end parallel
94 !ERROR: Argument `cc` on the ATTACH clause must be a variable or array with the POINTER or ALLOCATABLE attribute
95 !$acc parallel attach(dd, p, cc)
96 !$acc end parallel
98 !$acc parallel private(aa) firstprivate(bb, cc)
99 !$acc end parallel
101 !$acc parallel default(none)
102 !$acc end parallel
104 !$acc parallel default(present)
105 !$acc end parallel
107 !$acc parallel device_type(*)
108 !$acc end parallel
110 !$acc parallel device_type(1)
111 !$acc end parallel
113 !$acc parallel device_type(1, 3)
114 !$acc end parallel
116 !ERROR: Clause PRIVATE is not allowed after clause DEVICE_TYPE on the PARALLEL directive
117 !ERROR: Clause FIRSTPRIVATE is not allowed after clause DEVICE_TYPE on the PARALLEL directive
118 !$acc parallel device_type(*) private(aa) firstprivate(bb)
119 !$acc end parallel
121 !$acc parallel device_type(*) async
122 !$acc end parallel
124 !$acc parallel device_type(*) wait
125 !$acc end parallel
127 !$acc parallel device_type(*) num_gangs(8)
128 !$acc end parallel
130 !$acc parallel device_type(1) async device_type(2) wait
131 !$acc end parallel
133 !ERROR: Clause IF is not allowed after clause DEVICE_TYPE on the PARALLEL directive
134 !$acc parallel device_type(*) if(.TRUE.)
135 !$acc loop
136 do i = 1, N
137 a(i) = 3.14
138 end do
139 !$acc end parallel
141 end program openacc_parallel_validity