[flang] Accept polymorphic component element in storage_size
[llvm-project.git] / flang / test / Semantics / OpenACC / acc-branch.f90
blob9035775a3f765e211053bef5fe937b48601d76b7
1 ! RUN: %python %S/../test_errors.py %s %flang -fopenacc
3 ! Check OpenACC restruction in branch in and out of some construct
5 program openacc_clause_validity
7 implicit none
9 integer :: i, j, k
10 integer :: N = 256
11 real(8) :: a(256)
13 !$acc parallel
14 !$acc loop
15 do i = 1, N
16 a(i) = 3.14
17 !ERROR: RETURN statement is not allowed in a PARALLEL construct
18 return
19 end do
20 !$acc end parallel
22 !$acc parallel
23 !$acc loop
24 do i = 1, N
25 a(i) = 3.14
26 if(i == N-1) THEN
27 exit
28 end if
29 end do
30 !$acc end parallel
32 ! Exit branches out of parallel construct, not attached to an OpenACC parallel construct.
33 name1: do k=1, N
34 !$acc parallel
35 !$acc loop
36 outer: do i=1, N
37 inner: do j=1, N
38 ifname: if (j == 2) then
39 ! These are allowed.
40 exit
41 exit inner
42 exit outer
43 !ERROR: EXIT to construct 'name1' outside of PARALLEL construct is not allowed
44 exit name1
45 ! Exit to construct other than loops.
46 exit ifname
47 end if ifname
48 end do inner
49 end do outer
50 !$acc end parallel
51 end do name1
53 ! Exit branches out of parallel construct, attached to an OpenACC parallel construct.
54 thisblk: BLOCK
55 fortname: if (.true.) then
56 !PORTABILITY: The construct name 'name1' should be distinct at the subprogram level
57 name1: do k = 1, N
58 !$acc parallel
59 !ERROR: EXIT to construct 'fortname' outside of PARALLEL construct is not allowed
60 exit fortname
61 !$acc loop
62 do i = 1, N
63 a(i) = 3.14
64 if(i == N-1) THEN
65 !ERROR: EXIT to construct 'name1' outside of PARALLEL construct is not allowed
66 exit name1
67 end if
68 end do
70 loop2: do i = 1, N
71 a(i) = 3.33
72 !ERROR: EXIT to construct 'thisblk' outside of PARALLEL construct is not allowed
73 exit thisblk
74 end do loop2
75 !$acc end parallel
76 end do name1
77 end if fortname
78 end BLOCK thisblk
80 !Exit branches inside OpenACC construct.
81 !$acc parallel
82 !$acc loop
83 do i = 1, N
84 a(i) = 3.14
85 ifname: if (i == 2) then
86 ! This is allowed.
87 exit ifname
88 end if ifname
89 end do
90 !$acc end parallel
92 !$acc parallel
93 !$acc loop
94 do i = 1, N
95 a(i) = 3.14
96 if(i == N-1) THEN
97 stop 999 ! no error
98 end if
99 end do
100 !$acc end parallel
102 !$acc kernels
103 do i = 1, N
104 a(i) = 3.14
105 !ERROR: RETURN statement is not allowed in a KERNELS construct
106 return
107 end do
108 !$acc end kernels
110 !$acc kernels
111 do i = 1, N
112 a(i) = 3.14
113 if(i == N-1) THEN
114 exit
115 end if
116 end do
117 !$acc end kernels
119 !$acc kernels
120 do i = 1, N
121 a(i) = 3.14
122 if(i == N-1) THEN
123 stop 999 ! no error
124 end if
125 end do
126 !$acc end kernels
128 !$acc serial
129 do i = 1, N
130 a(i) = 3.14
131 !ERROR: RETURN statement is not allowed in a SERIAL construct
132 return
133 end do
134 !$acc end serial
136 !$acc serial
137 do i = 1, N
138 a(i) = 3.14
139 if(i == N-1) THEN
140 exit
141 end if
142 end do
143 !$acc end serial
145 name2: do k=1, N
146 !$acc serial
147 do i = 1, N
148 ifname: if (.true.) then
149 print *, "LGTM"
150 a(i) = 3.14
151 if(i == N-1) THEN
152 !ERROR: EXIT to construct 'name2' outside of SERIAL construct is not allowed
153 exit name2
154 exit ifname
155 end if
156 end if ifname
157 end do
158 !$acc end serial
159 end do name2
161 !$acc serial
162 do i = 1, N
163 a(i) = 3.14
164 if(i == N-1) THEN
165 stop 999 ! no error
166 end if
167 end do
168 !$acc end serial
170 end program openacc_clause_validity