
This is the first part of the effort to make parsing of clause modifiers more uniform and robust. Currently, when multiple modifiers are allowed, the parser will expect them to appear in a hard-coded order. Additionally, modifier properties (such as "ultimate") are checked separately for each case. The overall plan is 1. Extract all modifiers into their own top-level classes, and then equip them with sets of common properties that will allow performing the property checks generically, without refering to the specific kind of the modifier. 2. Define a parser (as a separate class) for each modifier. 3. For each clause define a union (std::variant) of all allowable modifiers, and parse the modifiers as a list of these unions. The intent is also to isolate parts of the code that could eventually be auto-generated. OpenMP modifier overhaul: #1/3
65 lines
2.2 KiB
Fortran
65 lines
2.2 KiB
Fortran
!RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=52 %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
|
|
!RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=52 %s | FileCheck --check-prefix="PARSE-TREE" %s
|
|
|
|
subroutine f00
|
|
integer :: x, y
|
|
!$omp depobj(x) depend(in: y)
|
|
end
|
|
|
|
!UNPARSE: SUBROUTINE f00
|
|
!UNPARSE: INTEGER x, y
|
|
!UNPARSE: !$OMP DEPOBJ(x) DEPEND(IN:y)
|
|
!UNPARSE: END SUBROUTINE
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPDepobjConstruct
|
|
!PARSE-TREE: | Verbatim
|
|
!PARSE-TREE: | OmpObject -> Designator -> DataRef -> Name = 'x'
|
|
!PARSE-TREE: | OmpClause -> Depend -> OmpDependClause -> TaskDep
|
|
!PARSE-TREE: | | OmpTaskDependenceType -> Value = In
|
|
!PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'y'
|
|
|
|
subroutine f01
|
|
integer :: x
|
|
!$omp depobj(x) update(out)
|
|
end
|
|
|
|
!UNPARSE: SUBROUTINE f01
|
|
!UNPARSE: INTEGER x
|
|
!UNPARSE: !$OMP DEPOBJ(x) UPDATE(OUT)
|
|
!UNPARSE: END SUBROUTINE
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPDepobjConstruct
|
|
!PARSE-TREE: | Verbatim
|
|
!PARSE-TREE: | OmpObject -> Designator -> DataRef -> Name = 'x'
|
|
!PARSE-TREE: | OmpClause -> Update -> OmpUpdateClause -> OmpTaskDependenceType -> Value = Out
|
|
|
|
subroutine f02
|
|
integer :: x
|
|
!$omp depobj(x) destroy(x)
|
|
end
|
|
|
|
!UNPARSE: SUBROUTINE f02
|
|
!UNPARSE: INTEGER x
|
|
!UNPARSE: !$OMP DEPOBJ(x) DESTROY(x)
|
|
!UNPARSE: END SUBROUTINE
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPDepobjConstruct
|
|
!PARSE-TREE: | Verbatim
|
|
!PARSE-TREE: | OmpObject -> Designator -> DataRef -> Name = 'x'
|
|
!PARSE-TREE: | OmpClause -> Destroy -> OmpDestroyClause -> OmpObject -> Designator -> DataRef -> Name = 'x'
|
|
|
|
subroutine f03
|
|
integer :: x
|
|
!$omp depobj(x) destroy
|
|
end
|
|
|
|
!UNPARSE: SUBROUTINE f03
|
|
!UNPARSE: INTEGER x
|
|
!UNPARSE: !$OMP DEPOBJ(x) DESTROY
|
|
!UNPARSE: END SUBROUTINE
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPDepobjConstruct
|
|
!PARSE-TREE: | Verbatim
|
|
!PARSE-TREE: | OmpObject -> Designator -> DataRef -> Name = 'x'
|
|
!PARSE-TREE: | OmpClause -> Destroy ->
|