1 ! RUN: %flang_fc1 -fdebug-unparse -fopenmp %s | FileCheck --ignore-case %s
2 ! RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp %s | FileCheck --check-prefix="PARSE-TREE" %s
4 ! Check for parsing of masked directive with filter clause.
7 subroutine test_masked()
9 !PARSE-TREE: OmpBeginBlockDirective
10 !PARSE-TREE-NEXT: OmpBlockDirective -> llvm::omp::Directive = masked
15 !PARSE-TREE: OmpBeginBlockDirective
16 !PARSE-TREE-NEXT: OmpBlockDirective -> llvm::omp::Directive = masked
17 !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Filter -> Scalar -> Integer -> Expr = '1_4'
18 !PARSE-TREE-NEXT: LiteralConstant -> IntLiteralConstant = '1'
19 !CHECK: !$omp masked filter(1_4)
20 !$omp masked filter(1)
25 subroutine test_masked_taskloop_simd()
27 !PARSE-TREE: OmpBeginLoopDirective
28 !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = masked taskloop simd
29 !CHECK: !$omp masked taskloop simd
30 !$omp masked taskloop simd
34 !$omp end masked taskloop simd
37 subroutine test_masked_taskloop
39 !PARSE-TREE: OmpBeginLoopDirective
40 !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = masked taskloop
41 !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Filter -> Scalar -> Integer -> Expr = '2_4'
42 !PARSE-TREE-NEXT: LiteralConstant -> IntLiteralConstant = '2'
43 !CHECK: !$omp masked taskloop filter(2_4)
44 !$omp masked taskloop filter(2)
48 !$omp end masked taskloop
51 subroutine test_parallel_masked
52 integer, parameter :: i
= 1, j
= 1
54 !PARSE-TREE: OmpBeginBlockDirective
55 !PARSE-TREE-NEXT: OmpBlockDirective -> llvm::omp::Directive = parallel masked
56 !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Filter -> Scalar -> Integer -> Expr = '2_4'
58 !PARSE-TREE-NEXT: Expr = '1_4'
59 !PARSE-TREE-NEXT: Designator -> DataRef -> Name = 'i'
60 !PARSE-TREE-NEXT: Expr = '1_4'
61 !PARSE-TREE-NEXT: Designator -> DataRef -> Name = 'j'
62 !CHECK: !$omp parallel masked filter(2_4)
63 !$omp parallel masked filter(i+j)
65 !$omp end parallel masked
68 subroutine test_parallel_masked_taskloop_simd
70 !PARSE-TREE: OmpBeginLoopDirective
71 !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = parallel masked taskloop simd
72 !CHECK: !$omp parallel masked taskloop simd
73 !$omp parallel masked taskloop simd
77 !$omp end parallel masked taskloop simd
80 subroutine test_parallel_masked_taskloop
82 !PARSE-TREE: OmpBeginLoopDirective
83 !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = parallel masked taskloop
84 !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Filter -> Scalar -> Integer -> Expr = '2_4'
85 !PARSE-TREE-NEXT: LiteralConstant -> IntLiteralConstant = '2'
86 !CHECK: !$omp parallel masked taskloop filter(2_4)
87 !$omp parallel masked taskloop filter(2)
91 !$omp end parallel masked taskloop