[Clang] Fix buildbot failure introduced by #121788
[llvm-project.git] / flang / test / Parser / OpenMP / lastprivate-clause.f90
blobac25174f3cc427fb2d20180b12f52ae2813dbb3e
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 foo1()
5 integer :: x, i
6 x = 1
7 !$omp parallel do lastprivate(x)
8 do i = 1, 100
9 x = x + 1
10 enddo
11 end
13 !UNPARSE: SUBROUTINE foo1
14 !UNPARSE: INTEGER x, i
15 !UNPARSE: x=1_4
16 !UNPARSE: !$OMP PARALLEL DO LASTPRIVATE(x)
17 !UNPARSE: DO i=1_4,100_4
18 !UNPARSE: x=x+1_4
19 !UNPARSE: END DO
20 !UNPARSE: END SUBROUTINE
22 !PARSE-TREE: SubroutineStmt
23 !PARSE-TREE: Name = 'foo1'
24 !PARSE-TREE: OmpLoopDirective -> llvm::omp::Directive = parallel do
25 !PARSE-TREE: OmpClauseList -> OmpClause -> Lastprivate -> OmpLastprivateClause
26 !PARSE-TREE: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
27 !PARSE-TREE: EndSubroutineStmt
30 subroutine foo2()
31 integer :: x, i
32 x = 1
33 !$omp parallel do lastprivate(conditional: x)
34 do i = 1, 100
35 x = x + 1
36 enddo
37 end
39 !UNPARSE: SUBROUTINE foo2
40 !UNPARSE: INTEGER x, i
41 !UNPARSE: x=1_4
42 !UNPARSE: !$OMP PARALLEL DO LASTPRIVATE(CONDITIONAL: x)
43 !UNPARSE: DO i=1_4,100_4
44 !UNPARSE: x=x+1_4
45 !UNPARSE: END DO
46 !UNPARSE: END SUBROUTINE
48 !PARSE-TREE: SubroutineStmt
49 !PARSE-TREE: Name = 'foo2'
50 !PARSE-TREE: OmpLoopDirective -> llvm::omp::Directive = parallel do
51 !PARSE-TREE: OmpClauseList -> OmpClause -> Lastprivate -> OmpLastprivateClause
52 !PARSE-TREE: Modifier -> OmpLastprivateModifier -> Value = Conditional
53 !PARSE-TREE: OmpObjectList -> OmpObject -> Designator -> DataRef -> Name = 'x'
54 !PARSE-TREE: EndSubroutineStmt