Skip to content

Commit 2546c6d

Browse files
authored
[flang][OpenMP] Recognize remaining OpenMP 6.0 spellings in parser (#147723)
Parse OpenMP 6.0 spellings for directives that don't use OmpDirectiveNameParser.
1 parent d2adfca commit 2546c6d

File tree

2 files changed

+266
-12
lines changed

2 files changed

+266
-12
lines changed

flang/lib/Parser/openmp-parsers.cpp

Lines changed: 14 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1500,7 +1500,7 @@ TYPE_PARSER(
15001500
// In this context "TARGET UPDATE" can be parsed as a TARGET directive
15011501
// followed by an UPDATE clause. This is the only combination at the
15021502
// moment, exclude it explicitly.
1503-
(!"TARGET UPDATE"_sptok) >=
1503+
(!("TARGET UPDATE"_sptok || "TARGET_UPDATE"_sptok)) >=
15041504
construct<OmpBlockDirective>(first(
15051505
"MASKED" >> pure(llvm::omp::Directive::OMPD_masked),
15061506
"MASTER" >> pure(llvm::omp::Directive::OMPD_master),
@@ -1513,6 +1513,7 @@ TYPE_PARSER(
15131513
"SCOPE" >> pure(llvm::omp::Directive::OMPD_scope),
15141514
"SINGLE" >> pure(llvm::omp::Directive::OMPD_single),
15151515
"TARGET DATA" >> pure(llvm::omp::Directive::OMPD_target_data),
1516+
"TARGET_DATA" >> pure(llvm::omp::Directive::OMPD_target_data),
15161517
"TARGET PARALLEL" >> pure(llvm::omp::Directive::OMPD_target_parallel),
15171518
"TARGET TEAMS" >> pure(llvm::omp::Directive::OMPD_target_teams),
15181519
"TARGET" >> pure(llvm::omp::Directive::OMPD_target),
@@ -1532,13 +1533,13 @@ TYPE_PARSER(construct<OmpInitializerClause>(
15321533
construct<OmpInitializerClause>(Parser<OmpInitializerProc>{})))
15331534

15341535
// OpenMP 5.2: 7.5.4 Declare Variant directive
1535-
TYPE_PARSER(sourced(
1536-
construct<OmpDeclareVariantDirective>(verbatim("DECLARE VARIANT"_tok),
1537-
"(" >> maybe(name / ":"), name / ")", Parser<OmpClauseList>{})))
1536+
TYPE_PARSER(sourced(construct<OmpDeclareVariantDirective>(
1537+
verbatim("DECLARE VARIANT"_tok) || verbatim("DECLARE_VARIANT"_tok),
1538+
"(" >> maybe(name / ":"), name / ")", Parser<OmpClauseList>{})))
15381539

15391540
// 2.16 Declare Reduction Construct
15401541
TYPE_PARSER(sourced(construct<OpenMPDeclareReductionConstruct>(
1541-
verbatim("DECLARE REDUCTION"_tok),
1542+
verbatim("DECLARE REDUCTION"_tok) || verbatim("DECLARE_REDUCTION"_tok),
15421543
"(" >> indirect(Parser<OmpReductionSpecifier>{}) / ")",
15431544
maybe(Parser<OmpClauseList>{}))))
15441545

@@ -1557,7 +1558,8 @@ TYPE_PARSER(
15571558

15581559
// 2.10.6 Declare Target Construct
15591560
TYPE_PARSER(sourced(construct<OpenMPDeclareTargetConstruct>(
1560-
verbatim("DECLARE TARGET"_tok), Parser<OmpDeclareTargetSpecifier>{})))
1561+
verbatim("DECLARE TARGET"_tok) || verbatim("DECLARE_TARGET"_tok),
1562+
Parser<OmpDeclareTargetSpecifier>{})))
15611563

15621564
static OmpMapperSpecifier ConstructOmpMapperSpecifier(
15631565
std::optional<Name> &&mapperName, TypeSpec &&typeSpec, Name &&varName) {
@@ -1584,9 +1586,9 @@ TYPE_PARSER(applyFunction<OmpMapperSpecifier>(ConstructOmpMapperSpecifier,
15841586
maybe(name / ":" / !":"_tok), typeSpec / "::", name))
15851587

15861588
// OpenMP 5.2: 5.8.8 Declare Mapper Construct
1587-
TYPE_PARSER(sourced(
1588-
construct<OpenMPDeclareMapperConstruct>(verbatim("DECLARE MAPPER"_tok),
1589-
parenthesized(Parser<OmpMapperSpecifier>{}), Parser<OmpClauseList>{})))
1589+
TYPE_PARSER(sourced(construct<OpenMPDeclareMapperConstruct>(
1590+
verbatim("DECLARE MAPPER"_tok) || verbatim("DECLARE_MAPPER"_tok),
1591+
parenthesized(Parser<OmpMapperSpecifier>{}), Parser<OmpClauseList>{})))
15901592

15911593
TYPE_PARSER(construct<OmpReductionCombiner>(Parser<AssignmentStmt>{}) ||
15921594
construct<OmpReductionCombiner>(Parser<FunctionReference>{}))
@@ -1631,9 +1633,9 @@ TYPE_PARSER(sourced(construct<OpenMPAllocatorsConstruct>(
16311633
TYPE_PARSER(construct<OmpEndAllocators>(startOmpLine >> "END ALLOCATORS"_tok))
16321634

16331635
// 2.8.2 Declare Simd construct
1634-
TYPE_PARSER(
1635-
sourced(construct<OpenMPDeclareSimdConstruct>(verbatim("DECLARE SIMD"_tok),
1636-
maybe(parenthesized(name)), Parser<OmpClauseList>{})))
1636+
TYPE_PARSER(sourced(construct<OpenMPDeclareSimdConstruct>(
1637+
verbatim("DECLARE SIMD"_tok) || verbatim("DECLARE_SIMD"_tok),
1638+
maybe(parenthesized(name)), Parser<OmpClauseList>{})))
16371639

16381640
// 2.4 Requires construct
16391641
TYPE_PARSER(sourced(construct<OpenMPRequiresConstruct>(
Lines changed: 252 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,252 @@
1+
!RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=60 %s -o - | FileCheck --check-prefix=UNPARSE %s
2+
!RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=60 %s -o - | FileCheck --check-prefix=PARSE-TREE %s
3+
4+
! The directives to check:
5+
! cancellation_point
6+
! declare_mapper
7+
! declare_reduction
8+
! declare_simd
9+
! declare_target
10+
! declare_variant
11+
! target_data
12+
! target_enter_data
13+
! target_exit_data
14+
! target_update
15+
16+
subroutine f00
17+
implicit none
18+
integer :: i
19+
20+
!$omp parallel
21+
do i = 1, 10
22+
!$omp cancellation_point parallel
23+
enddo
24+
!$omp end parallel
25+
end
26+
27+
!UNPARSE: SUBROUTINE f00
28+
!UNPARSE: IMPLICIT NONE
29+
!UNPARSE: INTEGER i
30+
!UNPARSE: !$OMP PARALLEL
31+
!UNPARSE: DO i=1_4,10_4
32+
!UNPARSE: !$OMP CANCELLATION_POINT PARALLEL
33+
!UNPARSE: END DO
34+
!UNPARSE: !$OMP END PARALLEL
35+
!UNPARSE: END SUBROUTINE
36+
37+
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPCancellationPointConstruct -> OmpDirectiveSpecification
38+
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = cancellation point
39+
!PARSE-TREE: | OmpClauseList -> OmpClause -> CancellationConstructType -> OmpCancellationConstructTypeClause
40+
!PARSE-TREE: | | OmpDirectiveName -> llvm::omp::Directive = parallel
41+
!PARSE-TREE: | Flags = None
42+
43+
subroutine f01
44+
type :: t
45+
integer :: x
46+
end type
47+
!$omp declare_mapper(t :: v) map(v%x)
48+
end
49+
50+
!UNPARSE: SUBROUTINE f01
51+
!UNPARSE: TYPE :: t
52+
!UNPARSE: INTEGER :: x
53+
!UNPARSE: END TYPE
54+
!UNPARSE: !$OMP DECLARE MAPPER (t::v) MAP(v%x)
55+
!UNPARSE: END SUBROUTINE
56+
57+
!PARSE-TREE: DeclarationConstruct -> SpecificationConstruct -> OpenMPDeclarativeConstruct -> OpenMPDeclareMapperConstruct
58+
!PARSE-TREE: | Verbatim
59+
!PARSE-TREE: | OmpMapperSpecifier
60+
!PARSE-TREE: | | string = 't.omp.default.mapper'
61+
!PARSE-TREE: | | TypeSpec -> DerivedTypeSpec
62+
!PARSE-TREE: | | | Name = 't'
63+
!PARSE-TREE: | | Name = 'v'
64+
!PARSE-TREE: | OmpClauseList -> OmpClause -> Map -> OmpMapClause
65+
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> StructureComponent
66+
!PARSE-TREE: | | | DataRef -> Name = 'v'
67+
!PARSE-TREE: | | | Name = 'x'
68+
!PARSE-TREE: | | bool = 'true'
69+
70+
subroutine f02
71+
type :: t
72+
integer :: x
73+
end type
74+
!$omp declare_reduction(+ : t : omp_out%x = omp_out%x + omp_in%x)
75+
end
76+
77+
!UNPARSE: SUBROUTINE f02
78+
!UNPARSE: TYPE :: t
79+
!UNPARSE: INTEGER :: x
80+
!UNPARSE: END TYPE
81+
!UNPARSE: !$OMP DECLARE REDUCTION (+:t: omp_out%x=omp_out%x+omp_in%x
82+
!UNPARSE: )
83+
!UNPARSE: END SUBROUTINE
84+
85+
!PARSE-TREE: DeclarationConstruct -> SpecificationConstruct -> OpenMPDeclarativeConstruct -> OpenMPDeclareReductionConstruct
86+
!PARSE-TREE: | Verbatim
87+
!PARSE-TREE: | OmpReductionSpecifier
88+
!PARSE-TREE: | | OmpReductionIdentifier -> DefinedOperator -> IntrinsicOperator = Add
89+
!PARSE-TREE: | | OmpTypeNameList -> OmpTypeSpecifier -> TypeSpec -> DerivedTypeSpec
90+
!PARSE-TREE: | | | Name = 't'
91+
!PARSE-TREE: | | OmpReductionCombiner -> AssignmentStmt = 'omp_out%x=omp_out%x+omp_in%x'
92+
!PARSE-TREE: | | | Variable = 'omp_out%x'
93+
!PARSE-TREE: | | | | Designator -> DataRef -> StructureComponent
94+
!PARSE-TREE: | | | | | DataRef -> Name = 'omp_out'
95+
!PARSE-TREE: | | | | | Name = 'x'
96+
!PARSE-TREE: | | | Expr = 'omp_out%x+omp_in%x'
97+
!PARSE-TREE: | | | | Add
98+
!PARSE-TREE: | | | | | Expr = 'omp_out%x'
99+
!PARSE-TREE: | | | | | | Designator -> DataRef -> StructureComponent
100+
!PARSE-TREE: | | | | | | | DataRef -> Name = 'omp_out'
101+
!PARSE-TREE: | | | | | | | Name = 'x'
102+
!PARSE-TREE: | | | | | Expr = 'omp_in%x'
103+
!PARSE-TREE: | | | | | | Designator -> DataRef -> StructureComponent
104+
!PARSE-TREE: | | | | | | | DataRef -> Name = 'omp_in'
105+
!PARSE-TREE: | | | | | | | Name = 'x'
106+
!PARSE-TREE: | OmpClauseList ->
107+
108+
subroutine f03
109+
!$omp declare_simd
110+
end
111+
112+
!UNPARSE: SUBROUTINE f03
113+
!UNPARSE: !$OMP DECLARE SIMD
114+
!UNPARSE: END SUBROUTINE
115+
116+
!PARSE-TREE: OpenMPDeclarativeConstruct -> OpenMPDeclareSimdConstruct
117+
!PARSE-TREE: | Verbatim
118+
!PARSE-TREE: | OmpClauseList ->
119+
120+
subroutine f04
121+
!$omp declare_target
122+
end
123+
124+
!UNPARSE: SUBROUTINE f04
125+
!UNPARSE: !$OMP DECLARE TARGET
126+
!UNPARSE: END SUBROUTINE
127+
128+
!PARSE-TREE: OpenMPDeclarativeConstruct -> OpenMPDeclareTargetConstruct
129+
!PARSE-TREE: | Verbatim
130+
!PARSE-TREE: | OmpDeclareTargetSpecifier -> OmpDeclareTargetWithClause -> OmpClauseList ->
131+
132+
subroutine f05
133+
implicit none
134+
interface
135+
subroutine g05
136+
end
137+
end interface
138+
!$omp declare_variant(g05) match(user={condition(.true.)})
139+
end
140+
141+
!UNPARSE: SUBROUTINE f05
142+
!UNPARSE: IMPLICIT NONE
143+
!UNPARSE: INTERFACE
144+
!UNPARSE: SUBROUTINE g05
145+
!UNPARSE: END SUBROUTINE
146+
!UNPARSE: END INTERFACE
147+
!UNPARSE: !$OMP DECLARE VARIANT (g05) MATCH(USER={CONDITION(.true._4)})
148+
!UNPARSE: END SUBROUTINE
149+
150+
!PARSE-TREE: OpenMPDeclarativeConstruct -> OmpDeclareVariantDirective
151+
!PARSE-TREE: | Verbatim
152+
!PARSE-TREE: | Name = 'g05'
153+
!PARSE-TREE: | OmpClauseList -> OmpClause -> Match -> OmpMatchClause -> OmpContextSelectorSpecification -> OmpTraitSetSelector
154+
!PARSE-TREE: | | OmpTraitSetSelectorName -> Value = User
155+
!PARSE-TREE: | | OmpTraitSelector
156+
!PARSE-TREE: | | | OmpTraitSelectorName -> Value = Condition
157+
!PARSE-TREE: | | | Properties
158+
!PARSE-TREE: | | | | OmpTraitProperty -> Scalar -> Expr = '.true._4'
159+
!PARSE-TREE: | | | | | LiteralConstant -> LogicalLiteralConstant
160+
!PARSE-TREE: | | | | | | bool = 'true'
161+
162+
subroutine f06
163+
implicit none
164+
integer :: i
165+
!$omp target_data map(tofrom: i)
166+
i = 0
167+
!$omp end target data
168+
end
169+
170+
!UNPARSE: SUBROUTINE f06
171+
!UNPARSE: IMPLICIT NONE
172+
!UNPARSE: INTEGER i
173+
!UNPARSE: !$OMP TARGET DATA MAP(TOFROM: i)
174+
!UNPARSE: i=0_4
175+
!UNPARSE: !$OMP END TARGET DATA
176+
!UNPARSE: END SUBROUTINE
177+
178+
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
179+
!PARSE-TREE: | OmpBeginBlockDirective
180+
!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target data
181+
!PARSE-TREE: | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
182+
!PARSE-TREE: | | | Modifier -> OmpMapType -> Value = Tofrom
183+
!PARSE-TREE: | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'i'
184+
!PARSE-TREE: | | | bool = 'true'
185+
!PARSE-TREE: | Block
186+
!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'i=0_4'
187+
!PARSE-TREE: | | | Variable = 'i'
188+
!PARSE-TREE: | | | | Designator -> DataRef -> Name = 'i'
189+
!PARSE-TREE: | | | Expr = '0_4'
190+
!PARSE-TREE: | | | | LiteralConstant -> IntLiteralConstant = '0'
191+
!PARSE-TREE: | OmpEndBlockDirective
192+
!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target data
193+
!PARSE-TREE: | | OmpClauseList ->
194+
195+
subroutine f07
196+
implicit none
197+
integer :: i
198+
!$omp target_enter_data map(to: i)
199+
end
200+
201+
!UNPARSE: SUBROUTINE f07
202+
!UNPARSE: IMPLICIT NONE
203+
!UNPARSE: INTEGER i
204+
!UNPARSE: !$OMP TARGET_ENTER_DATA MAP(TO: i)
205+
!UNPARSE: END SUBROUTINE
206+
207+
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct -> OmpDirectiveSpecification
208+
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = target enter data
209+
!PARSE-TREE: | OmpClauseList -> OmpClause -> Map -> OmpMapClause
210+
!PARSE-TREE: | | Modifier -> OmpMapType -> Value = To
211+
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'i'
212+
!PARSE-TREE: | | bool = 'true'
213+
!PARSE-TREE: | Flags = None
214+
215+
subroutine f08
216+
implicit none
217+
integer :: i
218+
!$omp target_exit_data map(from: i)
219+
end
220+
221+
!UNPARSE: SUBROUTINE f08
222+
!UNPARSE: IMPLICIT NONE
223+
!UNPARSE: INTEGER i
224+
!UNPARSE: !$OMP TARGET_EXIT_DATA MAP(FROM: i)
225+
!UNPARSE: END SUBROUTINE
226+
227+
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct -> OmpDirectiveSpecification
228+
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = target exit data
229+
!PARSE-TREE: | OmpClauseList -> OmpClause -> Map -> OmpMapClause
230+
!PARSE-TREE: | | Modifier -> OmpMapType -> Value = From
231+
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'i'
232+
!PARSE-TREE: | | bool = 'true'
233+
!PARSE-TREE: | Flags = None
234+
235+
subroutine f09
236+
implicit none
237+
integer :: i
238+
!$omp target_update to(i)
239+
end
240+
241+
!UNPARSE: SUBROUTINE f09
242+
!UNPARSE: IMPLICIT NONE
243+
!UNPARSE: INTEGER i
244+
!UNPARSE: !$OMP TARGET_UPDATE TO(i)
245+
!UNPARSE: END SUBROUTINE
246+
247+
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct -> OmpDirectiveSpecification
248+
!PARSE-TREE: | OmpDirectiveName -> llvm::omp::Directive = target update
249+
!PARSE-TREE: | OmpClauseList -> OmpClause -> To -> OmpToClause
250+
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'i'
251+
!PARSE-TREE: | | bool = 'true'
252+
!PARSE-TREE: | Flags = None

0 commit comments

Comments
 (0)