xref: /llvm-project/flang/test/Parser/OpenMP/target-loop-unparse.f90 (revision 608f4ae113f94b0c4a9b3c944a2aa9f115a805b4)
150e73aeeSKareem Ergawy! RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=50 %s | \
250e73aeeSKareem Ergawy! RUN:   FileCheck --ignore-case %s
3826bde5dSAnchu Rajendran S
450e73aeeSKareem Ergawy! RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=50 %s | \
550e73aeeSKareem Ergawy! RUN:   FileCheck --check-prefix="PARSE-TREE" %s
6826bde5dSAnchu Rajendran S
7826bde5dSAnchu Rajendran S! Check for parsing of loop directive
8826bde5dSAnchu Rajendran S
9826bde5dSAnchu Rajendran Ssubroutine test_loop
10826bde5dSAnchu Rajendran S  integer :: i, j = 1
11826bde5dSAnchu Rajendran S  !PARSE-TREE: OmpBeginLoopDirective
12826bde5dSAnchu Rajendran S  !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = loop
13826bde5dSAnchu Rajendran S  !CHECK: !$omp loop
14826bde5dSAnchu Rajendran S  !$omp loop
15826bde5dSAnchu Rajendran S  do i=1,10
16826bde5dSAnchu Rajendran S   j = j + 1
17826bde5dSAnchu Rajendran S  end do
18826bde5dSAnchu Rajendran S  !$omp end loop
1950e73aeeSKareem Ergawy
2050e73aeeSKareem Ergawy  !PARSE-TREE: OmpBeginLoopDirective
2150e73aeeSKareem Ergawy  !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = loop
22*608f4ae1SKrzysztof Parzyszek  !PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Bind -> OmpBindClause -> Binding = Thread
2350e73aeeSKareem Ergawy  !CHECK: !$omp loop
2450e73aeeSKareem Ergawy  !$omp loop bind(thread)
2550e73aeeSKareem Ergawy  do i=1,10
2650e73aeeSKareem Ergawy   j = j + 1
2750e73aeeSKareem Ergawy  end do
2850e73aeeSKareem Ergawy  !$omp end loop
29826bde5dSAnchu Rajendran Send subroutine
30826bde5dSAnchu Rajendran S
31826bde5dSAnchu Rajendran Ssubroutine test_target_loop
32826bde5dSAnchu Rajendran S  integer :: i, j = 1
33826bde5dSAnchu Rajendran S  !PARSE-TREE: OmpBeginLoopDirective
34826bde5dSAnchu Rajendran S  !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = target loop
35826bde5dSAnchu Rajendran S  !CHECK: !$omp target loop
36826bde5dSAnchu Rajendran S  !$omp target loop
37826bde5dSAnchu Rajendran S  do i=1,10
38826bde5dSAnchu Rajendran S   j = j + 1
39826bde5dSAnchu Rajendran S  end do
40826bde5dSAnchu Rajendran S  !$omp end target loop
41826bde5dSAnchu Rajendran Send subroutine
42826bde5dSAnchu Rajendran S
43826bde5dSAnchu Rajendran Ssubroutine test_target_teams_loop
44826bde5dSAnchu Rajendran S  integer :: i, j = 1
45826bde5dSAnchu Rajendran S  !PARSE-TREE: OmpBeginLoopDirective
46826bde5dSAnchu Rajendran S  !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = target teams loop
47826bde5dSAnchu Rajendran S  !CHECK: !$omp target teams loop
48826bde5dSAnchu Rajendran S  !$omp target teams loop
49826bde5dSAnchu Rajendran S  do i=1,10
50826bde5dSAnchu Rajendran S   j = j + 1
51826bde5dSAnchu Rajendran S  end do
52826bde5dSAnchu Rajendran S  !$omp end target teams loop
53826bde5dSAnchu Rajendran Send subroutine
54826bde5dSAnchu Rajendran S
55826bde5dSAnchu Rajendran Ssubroutine test_target_parallel_loop
56826bde5dSAnchu Rajendran S  integer :: i, j = 1
57826bde5dSAnchu Rajendran S  !PARSE-TREE: OmpBeginLoopDirective
58826bde5dSAnchu Rajendran S  !PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = target parallel loop
59826bde5dSAnchu Rajendran S  !CHECK: !$omp target parallel loop
60826bde5dSAnchu Rajendran S  !$omp target parallel loop
61826bde5dSAnchu Rajendran S  do i=1,10
62826bde5dSAnchu Rajendran S   j = j + 1
63826bde5dSAnchu Rajendran S  end do
64826bde5dSAnchu Rajendran S  !$omp end target parallel loop
65826bde5dSAnchu Rajendran Send subroutine
66