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 3 4! Check for parsing of masked directive with filter clause. 5 6 7subroutine test_masked() 8 integer :: c = 1 9 !PARSE-TREE: OmpBeginBlockDirective 10 !PARSE-TREE-NEXT: OmpBlockDirective -> llvm::omp::Directive = masked 11 !CHECK: !$omp masked 12 !$omp masked 13 c = c + 1 14 !$omp end 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) 21 c = c + 2 22 !$omp end masked 23end subroutine 24 25subroutine test_masked_taskloop_simd() 26 integer :: i, j = 1 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 31 do i=1,10 32 j = j + 1 33 end do 34 !$omp end masked taskloop simd 35end subroutine 36 37subroutine test_masked_taskloop 38 integer :: i, j = 1 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) 45 do i=1,10 46 j = j + 1 47 end do 48 !$omp end masked taskloop 49end subroutine 50 51subroutine test_parallel_masked 52 integer, parameter :: i = 1, j = 1 53 integer :: c = 2 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' 57 !PARSE-TREE-NEXT: Add 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) 64 c = c + 2 65 !$omp end parallel masked 66end subroutine 67 68subroutine test_parallel_masked_taskloop_simd 69 integer :: i, j = 1 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 74 do i=1,10 75 j = j + 1 76 end do 77 !$omp end parallel masked taskloop simd 78end subroutine 79 80subroutine test_parallel_masked_taskloop 81 integer :: i, j = 1 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) 88 do i=1,10 89 j = j + 1 90 end do 91 !$omp end parallel masked taskloop 92end subroutine 93