[Clang] Fix buildbot failure introduced by #121788
[llvm-project.git] / flang / test / Parser / OpenMP / affinity-clause.f90
blob642af6aeb7e491d59072b0718244846424416115
1 !RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=50 %s | FileCheck --ignore-case --check-prefix="UNPARSE" %s
2 !RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=50 %s | FileCheck --check-prefix="PARSE-TREE" %s
4 subroutine f00(x)
5 integer :: x(10)
6 !$omp task affinity(x)
7 x = x + 1
8 !$omp end task
9 end
11 !UNPARSE: SUBROUTINE f00 (x)
12 !UNPARSE: INTEGER x(10_4)
13 !UNPARSE: !$OMP TASK AFFINITY(x)
14 !UNPARSE: x=x+1_4
15 !UNPARSE: !$OMP END TASK
16 !UNPARSE: END SUBROUTINE
18 !PARSE-TREE: OmpBeginBlockDirective
19 !PARSE-TREE: | OmpBlockDirective -> llvm::omp::Directive = task
20 !PARSE-TREE: | OmpClauseList -> OmpClause -> Affinity -> OmpAffinityClause
21 !PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
23 subroutine f01(x)
24 integer :: x(10)
25 !$omp task affinity(x(1), x(3))
26 x = x + 1
27 !$omp end task
28 end
30 !UNPARSE: SUBROUTINE f01 (x)
31 !UNPARSE: INTEGER x(10_4)
32 !UNPARSE: !$OMP TASK AFFINITY(x(1_4),x(3_4))
33 !UNPARSE: x=x+1_4
34 !UNPARSE: !$OMP END TASK
35 !UNPARSE: END SUBROUTINE
37 !PARSE-TREE: OmpBeginBlockDirective
38 !PARSE-TREE: | OmpBlockDirective -> llvm::omp::Directive = task
39 !PARSE-TREE: | OmpClauseList -> OmpClause -> Affinity -> OmpAffinityClause
40 !PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> ArrayElement
41 !PARSE-TREE: | | | DataRef -> Name = 'x'
42 !PARSE-TREE: | | | SectionSubscript -> Integer -> Expr = '1_4'
43 !PARSE-TREE: | | | | LiteralConstant -> IntLiteralConstant = '1'
44 !PARSE-TREE: | | OmpObject -> Designator -> DataRef -> ArrayElement
45 !PARSE-TREE: | | | DataRef -> Name = 'x'
46 !PARSE-TREE: | | | SectionSubscript -> Integer -> Expr = '3_4'
47 !PARSE-TREE: | | | | LiteralConstant -> IntLiteralConstant = '3'
49 subroutine f02(x)
50 integer :: x(10)
51 !$omp task affinity(iterator(i = 1:3): x(i))
52 x = x + 1
53 !$omp end task
54 end
56 !UNPARSE: SUBROUTINE f02 (x)
57 !UNPARSE: INTEGER x(10_4)
58 !UNPARSE: !$OMP TASK AFFINITY(ITERATOR(INTEGER i = 1_4:3_4): x(i))
59 !UNPARSE: x=x+1_4
60 !UNPARSE: !$OMP END TASK
61 !UNPARSE: END SUBROUTINE
63 !PARSE-TREE: OmpBeginBlockDirective
64 !PARSE-TREE: | OmpBlockDirective -> llvm::omp::Directive = task
65 !PARSE-TREE: | OmpClauseList -> OmpClause -> Affinity -> OmpAffinityClause
66 !PARSE-TREE: | | Modifier -> OmpIterator -> OmpIteratorSpecifier
67 !PARSE-TREE: | | | TypeDeclarationStmt
68 !PARSE-TREE: | | | | DeclarationTypeSpec -> IntrinsicTypeSpec -> IntegerTypeSpec ->
69 !PARSE-TREE: | | | | EntityDecl
70 !PARSE-TREE: | | | | | Name = 'i'
71 !PARSE-TREE: | | | SubscriptTriplet
72 !PARSE-TREE: | | | | Scalar -> Integer -> Expr = '1_4'
73 !PARSE-TREE: | | | | | LiteralConstant -> IntLiteralConstant = '1'
74 !PARSE-TREE: | | | | Scalar -> Integer -> Expr = '3_4'
75 !PARSE-TREE: | | | | | LiteralConstant -> IntLiteralConstant = '3'
76 !PARSE-TREE: | | OmpObjectList -> OmpObject -> Designator -> DataRef -> ArrayElement
77 !PARSE-TREE: | | | DataRef -> Name = 'x'
78 !PARSE-TREE: | | | SectionSubscript -> Integer -> Expr = 'i'
79 !PARSE-TREE: | | | | Designator -> DataRef -> Name = 'i'