[Clang] Fix buildbot failure introduced by #121788
[llvm-project.git] / flang / test / Parser / OpenMP / bind-clause.f90
blob5f1e6b47f1c8d971df7bb31537dc1bd78ab36642
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
5 !$omp loop bind(parallel)
6 do i = 1, 10
7 continue
8 enddo
9 !$omp end loop
10 end
12 !UNPARSE: SUBROUTINE f00
13 !UNPARSE: !$OMP LOOP BIND(PARALLEL)
14 !UNPARSE: DO i=1_4,10_4
15 !UNPARSE: CONTINUE
16 !UNPARSE: END DO
17 !UNPARSE: !$OMP END LOOP
18 !UNPARSE: END SUBROUTINE
20 !PARSE-TREE: ExecutionPartConstruct -> ExecutableConstruct -> OpenMPConstruct -> OpenMPLoopConstruct
21 !PARSE-TREE: | OmpBeginLoopDirective
22 !PARSE-TREE: | | OmpLoopDirective -> llvm::omp::Directive = loop
23 !PARSE-TREE: | | OmpClauseList -> OmpClause -> Bind -> OmpBindClause -> Binding = Parallel
24 !PARSE-TREE: | DoConstruct