aboutsummaryrefslogtreecommitdiff
path: root/flang/test/Parser
diff options
context:
space:
mode:
Diffstat (limited to 'flang/test/Parser')
-rw-r--r--flang/test/Parser/OpenMP/block-construct.f90165
-rw-r--r--flang/test/Parser/OpenMP/construct-prefix-conflict.f90168
2 files changed, 333 insertions, 0 deletions
diff --git a/flang/test/Parser/OpenMP/block-construct.f90 b/flang/test/Parser/OpenMP/block-construct.f90
new file mode 100644
index 0000000..83f0f7f
--- /dev/null
+++ b/flang/test/Parser/OpenMP/block-construct.f90
@@ -0,0 +1,165 @@
+!RUN: %flang_fc1 -fdebug-unparse -fopenmp %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
+!RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp %s | FileCheck --check-prefix="PARSE-TREE" %s
+
+subroutine f00(x, y)
+ implicit none
+ integer :: x, y
+ !$omp target map(x, y)
+ x = y + 1
+ y = 2 * x
+ !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f00 (x, y)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x, y
+!UNPARSE: !$OMP TARGET MAP(x,y)
+!UNPARSE: x=y+1_4
+!UNPARSE: y=2_4*x
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
+!PARSE-TREE: | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | OmpObject -> Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | bool = 'true'
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'x=y+1_4'
+!PARSE-TREE: | | | Variable = 'x'
+!PARSE-TREE: | | | | Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | Expr = 'y+1_4'
+!PARSE-TREE: | | | | Add
+!PARSE-TREE: | | | | | Expr = 'y'
+!PARSE-TREE: | | | | | | Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | | | Expr = '1_4'
+!PARSE-TREE: | | | | | | LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'y=2_4*x'
+!PARSE-TREE: | | | Variable = 'y'
+!PARSE-TREE: | | | | Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | Expr = '2_4*x'
+!PARSE-TREE: | | | | Multiply
+!PARSE-TREE: | | | | | Expr = '2_4'
+!PARSE-TREE: | | | | | | LiteralConstant -> IntLiteralConstant = '2'
+!PARSE-TREE: | | | | | Expr = 'x'
+!PARSE-TREE: | | | | | | Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | OmpEndBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+
+
+subroutine f01(x, y)
+ implicit none
+ integer :: x, y
+ !$omp target map(x, y)
+ block
+ x = y + 1
+ y = 2 * x
+ endblock
+ ! No end-directive
+end
+
+!UNPARSE: SUBROUTINE f01 (x, y)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x, y
+!UNPARSE: !$OMP TARGET MAP(x,y)
+!UNPARSE: BLOCK
+!UNPARSE: x=y+1_4
+!UNPARSE: y=2_4*x
+!UNPARSE: END BLOCK
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
+!PARSE-TREE: | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | OmpObject -> Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | bool = 'true'
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> BlockConstruct
+!PARSE-TREE: | | | BlockStmt ->
+!PARSE-TREE: | | | BlockSpecificationPart -> SpecificationPart
+!PARSE-TREE: | | | | ImplicitPart ->
+!PARSE-TREE: | | | Block
+!PARSE-TREE: | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'x=y+1_4'
+!PARSE-TREE: | | | | | Variable = 'x'
+!PARSE-TREE: | | | | | | Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | | Expr = 'y+1_4'
+!PARSE-TREE: | | | | | | Add
+!PARSE-TREE: | | | | | | | Expr = 'y'
+!PARSE-TREE: | | | | | | | | Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | | | | | Expr = '1_4'
+!PARSE-TREE: | | | | | | | | LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'y=2_4*x'
+!PARSE-TREE: | | | | | Variable = 'y'
+!PARSE-TREE: | | | | | | Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | | | Expr = '2_4*x'
+!PARSE-TREE: | | | | | | Multiply
+!PARSE-TREE: | | | | | | | Expr = '2_4'
+!PARSE-TREE: | | | | | | | | LiteralConstant -> IntLiteralConstant = '2'
+!PARSE-TREE: | | | | | | | Expr = 'x'
+!PARSE-TREE: | | | | | | | | Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | EndBlockStmt ->
+
+
+subroutine f02(x, y)
+ implicit none
+ integer :: x, y
+ !$omp target map(x, y)
+ block
+ x = y + 1
+ y = 2 * x
+ endblock
+ ! End-directive present
+ !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f02 (x, y)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x, y
+!UNPARSE: !$OMP TARGET MAP(x,y)
+!UNPARSE: BLOCK
+!UNPARSE: x=y+1_4
+!UNPARSE: y=2_4*x
+!UNPARSE: END BLOCK
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
+!PARSE-TREE: | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | OmpObject -> Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | bool = 'true'
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> BlockConstruct
+!PARSE-TREE: | | | BlockStmt ->
+!PARSE-TREE: | | | BlockSpecificationPart -> SpecificationPart
+!PARSE-TREE: | | | | ImplicitPart ->
+!PARSE-TREE: | | | Block
+!PARSE-TREE: | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'x=y+1_4'
+!PARSE-TREE: | | | | | Variable = 'x'
+!PARSE-TREE: | | | | | | Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | | Expr = 'y+1_4'
+!PARSE-TREE: | | | | | | Add
+!PARSE-TREE: | | | | | | | Expr = 'y'
+!PARSE-TREE: | | | | | | | | Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | | | | | Expr = '1_4'
+!PARSE-TREE: | | | | | | | | LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt = 'y=2_4*x'
+!PARSE-TREE: | | | | | Variable = 'y'
+!PARSE-TREE: | | | | | | Designator -> DataRef -> Name = 'y'
+!PARSE-TREE: | | | | | Expr = '2_4*x'
+!PARSE-TREE: | | | | | | Multiply
+!PARSE-TREE: | | | | | | | Expr = '2_4'
+!PARSE-TREE: | | | | | | | | LiteralConstant -> IntLiteralConstant = '2'
+!PARSE-TREE: | | | | | | | Expr = 'x'
+!PARSE-TREE: | | | | | | | | Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | EndBlockStmt ->
+!PARSE-TREE: | OmpEndBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
diff --git a/flang/test/Parser/OpenMP/construct-prefix-conflict.f90 b/flang/test/Parser/OpenMP/construct-prefix-conflict.f90
new file mode 100644
index 0000000..678942a
--- /dev/null
+++ b/flang/test/Parser/OpenMP/construct-prefix-conflict.f90
@@ -0,0 +1,168 @@
+!RUN: %flang_fc1 -fdebug-unparse-no-sema -fopenmp %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
+!RUN: %flang_fc1 -fdebug-dump-parse-tree-no-sema -fopenmp %s | FileCheck --check-prefix="PARSE-TREE" %s
+
+! Check that constructs A and B are parsed correctly, where the name of A
+! is a prefix of B.
+! Currently it's TARGET vs TARGET DATA, TARGET ENTER DATA, TARGET EXIT DATA,
+! and TARGET UPDATE.
+
+subroutine f00(x)
+ implicit none
+ integer :: x
+ !$omp target
+ !$omp target data map(x)
+ x = x + 1
+ !$omp end target data
+ !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f00 (x)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x
+!UNPARSE: !$OMP TARGET
+!UNPARSE: !$OMP TARGET DATA MAP(x)
+!UNPARSE: x = x+1
+!UNPARSE: !$OMP END TARGET DATA
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | | | OmpBeginBlockDirective
+!PARSE-TREE: | | | | OmpBlockDirective -> llvm::omp::Directive = target data
+!PARSE-TREE: | | | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
+!PARSE-TREE: | | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | | bool = 'true'
+!PARSE-TREE: | | | Block
+!PARSE-TREE: | | | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt
+!PARSE-TREE: | | | | | Variable -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | | Expr -> Add
+!PARSE-TREE: | | | | | | Expr -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | | | Expr -> LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | | | OmpEndBlockDirective
+!PARSE-TREE: | | | | OmpBlockDirective -> llvm::omp::Directive = target data
+!PARSE-TREE: | | | | OmpClauseList ->
+!PARSE-TREE: | OmpEndBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+
+
+subroutine f01(x)
+ implicit none
+ integer :: x
+ !$omp target
+ !$omp target enter data map(x)
+ x = x + 1
+ !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f01 (x)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x
+!UNPARSE: !$OMP TARGET
+!UNPARSE: !$OMP TARGET ENTER DATA MAP(x)
+!UNPARSE: x = x+1
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct -> OmpDirectiveSpecification
+!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = target enter data
+!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
+!PARSE-TREE: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | bool = 'true'
+!PARSE-TREE: | | | Flags = None
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt
+!PARSE-TREE: | | | Variable -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | Expr -> Add
+!PARSE-TREE: | | | | Expr -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | Expr -> LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | OmpEndBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+
+
+subroutine f02(x)
+ implicit none
+ integer :: x
+ !$omp target
+ !$omp target exit data map(x)
+ x = x + 1
+ !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f02 (x)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x
+!UNPARSE: !$OMP TARGET
+!UNPARSE: !$OMP TARGET EXIT DATA MAP(x)
+!UNPARSE: x = x+1
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct -> OmpDirectiveSpecification
+!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = target exit data
+!PARSE-TREE: | | | OmpClauseList -> OmpClause -> Map -> OmpMapClause
+!PARSE-TREE: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | bool = 'true'
+!PARSE-TREE: | | | Flags = None
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt
+!PARSE-TREE: | | | Variable -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | Expr -> Add
+!PARSE-TREE: | | | | Expr -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | Expr -> LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | OmpEndBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+
+
+subroutine f03(x)
+ implicit none
+ integer :: x
+ !$omp target
+ !$omp target update to(x)
+ x = x + 1
+ !$omp end target
+end
+
+!UNPARSE: SUBROUTINE f03 (x)
+!UNPARSE: IMPLICIT NONE
+!UNPARSE: INTEGER x
+!UNPARSE: !$OMP TARGET
+!UNPARSE: !$OMP TARGET UPDATE TO(x)
+!UNPARSE: x = x+1
+!UNPARSE: !$OMP END TARGET
+!UNPARSE: END SUBROUTINE
+
+!PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPBlockConstruct
+!PARSE-TREE: | OmpBeginBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->
+!PARSE-TREE: | Block
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct -> OmpDirectiveSpecification
+!PARSE-TREE: | | | OmpDirectiveName -> llvm::omp::Directive = target update
+!PARSE-TREE: | | | OmpClauseList -> OmpClause -> To -> OmpToClause
+!PARSE-TREE: | | | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | bool = 'true'
+!PARSE-TREE: | | | Flags = None
+!PARSE-TREE: | | ExecutionPartConstruct -> ExecutableConstruct -> ActionStmt -> AssignmentStmt
+!PARSE-TREE: | | | Variable -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | Expr -> Add
+!PARSE-TREE: | | | | Expr -> Designator -> DataRef -> Name = 'x'
+!PARSE-TREE: | | | | Expr -> LiteralConstant -> IntLiteralConstant = '1'
+!PARSE-TREE: | OmpEndBlockDirective
+!PARSE-TREE: | | OmpBlockDirective -> llvm::omp::Directive = target
+!PARSE-TREE: | | OmpClauseList ->