
The structure is - OmpBeginDirective (aka OmpDirectiveSpecification) - Block - optional<OmpEndDirective> (aka optional<OmpDirectiveSpecification>) The OmpBeginDirective and OmpEndDirective are effectively different names for OmpDirectiveSpecification. They exist to allow the semantic analyses to distinguish between the beginning and the ending of a block construct without maintaining additional context. The actual changes are in the parser: parse-tree.h and openmp-parser.cpp in particular. The rest is simply changing the way the directive/clause information is accessed (typically for the simpler). All standalone and block constructs now use OmpDirectiveSpecification to store the directive/clause information.
25 lines
970 B
Fortran
25 lines
970 B
Fortran
! RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=51 %s | FileCheck --ignore-case %s
|
|
! RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=51 %s | FileCheck --check-prefix="PARSE-TREE" %s
|
|
|
|
program omp_scope
|
|
integer i
|
|
i = 10
|
|
|
|
!CHECK: !$OMP SCOPE PRIVATE(i)
|
|
!CHECK: !$OMP END SCOPE
|
|
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
|
|
!PARSE-TREE: OmpBeginDirective
|
|
!PARSE-TREE: OmpDirectiveName -> llvm::omp::Directive = scope
|
|
!PARSE-TREE: OmpClauseList -> OmpClause -> Private -> OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'i'
|
|
!PARSE-TREE: Block
|
|
!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> PrintStmt
|
|
!PARSE-TREE: OmpEndDirective
|
|
!PARSE-TREE: OmpDirectiveName -> llvm::omp::Directive = scope
|
|
!PARSE-TREE: OmpClauseList -> OmpClause -> Nowait
|
|
|
|
!$omp scope private(i)
|
|
print *, "omp scope", i
|
|
!$omp end scope nowait
|
|
end program omp_scope
|