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