Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / OpenMP / sections02.f90
blobbcdeb05e5a171ca040f1aae1cf5ee1d98998dddc
1 ! RUN: %python %S/../test_errors.py %s %flang -fopenmp
2 ! OpenMP version 5.0.0
3 ! 2.8.1 sections construct
4 ! The code enclosed in a sections construct must be a structured block.
5 program OmpConstructSections01
6 use omp_lib
7 integer :: section_count = 0
8 integer, parameter :: NT = 4
9 print *, 'section_count', section_count
10 !ERROR: invalid branch into an OpenMP structured block
11 !ERROR: invalid branch into an OpenMP structured block
12 !ERROR: invalid branch into an OpenMP structured block
13 if (NT) 20, 30, 40
14 !ERROR: invalid branch into an OpenMP structured block
15 goto 20
16 !$omp sections
17 !$omp section
18 print *, "This is a single statement structured block"
19 !$omp section
20 open (10, file="random-file-name.txt", err=30)
21 !ERROR: invalid branch into an OpenMP structured block
22 !ERROR: invalid branch leaving an OpenMP structured block
23 open (10, file="random-file-name.txt", err=40)
24 !$omp section
25 section_count = section_count + 1
26 20 print *, 'Entering into section'
27 call calledFromWithinSection()
28 print *, 'section_count', section_count
29 !$omp section
30 section_count = section_count + 1
31 print *, 'section_count', section_count
32 !ERROR: invalid branch leaving an OpenMP structured block
33 goto 10
34 !$omp section
35 30 print *, "Error in opening file"
36 !$omp end sections
37 10 print *, 'Jump from section'
39 !$omp sections
40 !$omp section
41 40 print *, 'Error in opening file'
42 !$omp end sections
43 end program OmpConstructSections01
45 function returnFromSections()
46 !$omp sections
47 !$omp section
48 !ERROR: RETURN statement is not allowed in a SECTIONS construct
49 RETURN
50 !$omp end sections
51 end function
53 subroutine calledFromWithinSection()
54 print *, "I am called from within a 'section' structured block"
55 return
56 end subroutine calledFromWithinSection
58 subroutine continueWithinSections()
59 integer i
60 do i = 1, 10
61 print *, "Statement within loop but outside section construct"
62 !$omp sections
63 !$omp section
64 IF (i .EQ. 5) THEN
65 !ERROR: CYCLE to construct outside of SECTIONS construct is not allowed
66 CYCLE
67 END IF
68 !$omp end sections
69 print *, "Statement within loop but outside section contruct"
70 end do
72 !$omp sections
73 !$omp section
74 do i = 1, 10
75 CYCLE
76 end do
77 !$omp end sections
79 !$omp sections
80 !$omp section
81 loop_1: do i = 1, 10
82 IF (i .EQ. 5) THEN
83 CYCLE loop_1
84 END IF
85 end do loop_1
86 !$omp end sections
88 loop_2: do i = 1, 10
89 !$omp sections
90 !$omp section
91 IF (i .EQ. 5) THEN
92 !ERROR: CYCLE to construct 'loop_2' outside of SECTIONS construct is not allowed
93 CYCLE loop_2
94 END IF
95 !$omp end sections
96 end do loop_2
97 end subroutine continueWithinSections
99 subroutine breakWithinSections()
100 loop_3: do i = 1, 10
101 !$omp sections
102 !$omp section
103 IF (i .EQ. 5) THEN
104 !ERROR: EXIT to construct 'loop_3' outside of SECTIONS construct is not allowed
105 EXIT loop_3
106 END IF
107 !$omp end sections
108 end do loop_3
110 loop_4: do i = 1, 10
111 !$omp sections
112 !$omp section
113 IF (i .EQ. 5) THEN
114 !ERROR: EXIT to construct outside of SECTIONS construct is not allowed
115 EXIT
116 END IF
117 !$omp end sections
118 end do loop_4
120 !$omp sections
121 !$omp section
122 do i = 1, 10
123 IF (i .EQ. 5) THEN
124 EXIT
125 END IF
126 end do
127 !$omp end sections
129 !$omp sections
130 !$omp section
131 loop_5: do i = 1, 10
132 IF (i .EQ. 5) THEN
133 EXIT loop_5
134 END IF
135 end do loop_5
136 !$omp end sections
137 end subroutine breakWithinSections