xref: /llvm-project/flang/test/Parser/OpenMP/scan.f90 (revision e67e09a77ea1e4802c0f6bc0409c9f5e9d1fae9a)
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 scan directive
5subroutine test_scan(n, a, b)
6  implicit none
7  integer n
8  integer a(n), b(n)
9  integer x,y,k
10
11  ! a(k) is included in the computation of producing results in b(k)
12  !$omp parallel do simd reduction(inscan,+: x)
13  do k = 1, n
14    x = x + a(k)
15    !PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct
16    !PARSE-TREE-NEXT: OmpSimpleStandaloneDirective -> llvm::omp::Directive = scan
17    !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Inclusive -> OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
18    !CHECK: !$omp scan inclusive(x)
19    !$omp scan inclusive(x)
20      b(k) = x
21  end do
22
23  ! a(k) is not included in the computation of producing results in b(k)
24  !$omp parallel do simd reduction(inscan,+: x)
25  do k = 1, n
26    b(k) = x
27    !PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct
28    !PARSE-TREE-NEXT: OmpSimpleStandaloneDirective -> llvm::omp::Directive = scan
29    !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Exclusive -> OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
30    !CHECK: !$omp scan exclusive(x)
31    !$omp scan exclusive(x)
32    x = x + a(k)
33  end do
34
35  !$omp parallel do simd reduction(inscan,+: x, y)
36  do k = 1, n
37    x = x + a(k)
38    !PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct
39    !PARSE-TREE-NEXT: OmpSimpleStandaloneDirective -> llvm::omp::Directive = scan
40    !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Inclusive -> OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
41    !PARSE-TREE-NEXT: OmpObject -> Designator -> DataRef -> Name = 'y'
42    !CHECK: !$omp scan inclusive(x,y)
43    !$omp scan inclusive(x, y)
44      b(k) = x
45  end do
46
47  !$omp parallel do simd reduction(inscan,+: x, y)
48  do k = 1, n
49    x = x + a(k)
50    !PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPStandaloneConstruct -> OpenMPSimpleStandaloneConstruct
51    !PARSE-TREE-NEXT: OmpSimpleStandaloneDirective -> llvm::omp::Directive = scan
52    !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Exclusive -> OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
53    !PARSE-TREE-NEXT: OmpObject -> Designator -> DataRef -> Name = 'y'
54    !CHECK: !$omp scan exclusive(x,y)
55    !$omp scan exclusive(x, y)
56      b(k) = x
57  end do
58end subroutine
59