[AArch64] Fix brackets warning in assert. NFC
[llvm-project.git] / flang / test / Semantics / OpenACC / acc-init-validity.f90
blob3b594a25217c0945839f2991bcb3194f2c2cea55
1 ! RUN: %python %S/../test_errors.py %s %flang -fopenacc
3 ! Check OpenACC clause validity for the following construct and directive:
4 ! 2.14.1 Init
6 program openacc_init_validity
8 implicit none
10 integer :: i, j
11 integer, parameter :: N = 256
12 logical :: ifCondition = .TRUE.
13 integer :: ifInt
14 real :: ifReal
15 real(8), dimension(N) :: a
17 !$acc init
18 !$acc init if(.TRUE.)
19 !$acc init if(ifCondition)
20 !$acc init if(ifInt)
21 !$acc init device_num(1)
22 !$acc init device_num(i)
23 !$acc init device_type(default)
24 !$acc init device_type(nvidia, radeon)
25 !$acc init device_num(i) device_type(host, multicore) if(ifCondition)
27 !$acc parallel
28 !ERROR: Directive INIT may not be called within a compute region
29 !$acc init
30 !$acc end parallel
32 !$acc serial
33 !ERROR: Directive INIT may not be called within a compute region
34 !$acc init
35 !$acc end serial
37 !$acc kernels
38 !ERROR: Directive INIT may not be called within a compute region
39 !$acc init
40 !$acc end kernels
42 !$acc parallel
43 !$acc loop
44 do i = 1, N
45 !ERROR: Directive INIT may not be called within a compute region
46 !$acc init
47 a(i) = 3.14
48 end do
49 !$acc end parallel
51 !$acc serial
52 !$acc loop
53 do i = 1, N
54 !ERROR: Directive INIT may not be called within a compute region
55 !$acc init
56 a(i) = 3.14
57 end do
58 !$acc end serial
60 !$acc kernels
61 !$acc loop
62 do i = 1, N
63 !ERROR: Directive INIT may not be called within a compute region
64 !$acc init
65 a(i) = 3.14
66 end do
67 !$acc end kernels
69 !$acc parallel loop
70 do i = 1, N
71 !ERROR: Directive INIT may not be called within a compute region
72 !$acc init
73 a(i) = 3.14
74 end do
76 !$acc serial loop
77 do i = 1, N
78 !ERROR: Directive INIT may not be called within a compute region
79 !$acc init
80 a(i) = 3.14
81 end do
83 !$acc kernels loop
84 do i = 1, N
85 !ERROR: Directive INIT may not be called within a compute region
86 !$acc init
87 a(i) = 3.14
88 end do
90 !ERROR: At most one IF clause can appear on the INIT directive
91 !$acc init if(.TRUE.) if(ifCondition)
93 !ERROR: At most one DEVICE_NUM clause can appear on the INIT directive
94 !$acc init device_num(1) device_num(i)
96 !ERROR: At most one DEVICE_TYPE clause can appear on the INIT directive
97 !$acc init device_type(nvidia) device_type(default, *)
99 !ERROR: Must have LOGICAL or INTEGER type
100 !$acc init if(ifReal)
102 end program openacc_init_validity