Files
clang-p2996/flang/test/Parser/OpenMP/target-loop-unparse.f90
Krzysztof Parzyszek 608f4ae113 [flang][OpenMP] Rename some Type members in OpenMP clauses (#117784)
The intent is to keep names in sync with the terminology from the OpenMP
spec:
```
  OmpBindClause::Type       -> Binding
  OmpDefaultClause::Type    -> DataSharingAttribute
  OmpDeviceTypeClause::Type -> DeviceTypeDescription
  OmpProcBindClause::Type   -> AffinityPolicy
```
Add more comments with references to the OpenMP specs.
2024-12-02 09:22:30 -06:00

66 lines
1.7 KiB
Fortran

! RUN: %flang_fc1 -fdebug-unparse -fopenmp -fopenmp-version=50 %s | \
! RUN: FileCheck --ignore-case %s
! RUN: %flang_fc1 -fdebug-dump-parse-tree -fopenmp -fopenmp-version=50 %s | \
! RUN: FileCheck --check-prefix="PARSE-TREE" %s
! Check for parsing of loop directive
subroutine test_loop
integer :: i, j = 1
!PARSE-TREE: OmpBeginLoopDirective
!PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = loop
!CHECK: !$omp loop
!$omp loop
do i=1,10
j = j + 1
end do
!$omp end loop
!PARSE-TREE: OmpBeginLoopDirective
!PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = loop
!PARSE-TREE-NEXT: OmpClauseList -> OmpClause -> Bind -> OmpBindClause -> Binding = Thread
!CHECK: !$omp loop
!$omp loop bind(thread)
do i=1,10
j = j + 1
end do
!$omp end loop
end subroutine
subroutine test_target_loop
integer :: i, j = 1
!PARSE-TREE: OmpBeginLoopDirective
!PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = target loop
!CHECK: !$omp target loop
!$omp target loop
do i=1,10
j = j + 1
end do
!$omp end target loop
end subroutine
subroutine test_target_teams_loop
integer :: i, j = 1
!PARSE-TREE: OmpBeginLoopDirective
!PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = target teams loop
!CHECK: !$omp target teams loop
!$omp target teams loop
do i=1,10
j = j + 1
end do
!$omp end target teams loop
end subroutine
subroutine test_target_parallel_loop
integer :: i, j = 1
!PARSE-TREE: OmpBeginLoopDirective
!PARSE-TREE-NEXT: OmpLoopDirective -> llvm::omp::Directive = target parallel loop
!CHECK: !$omp target parallel loop
!$omp target parallel loop
do i=1,10
j = j + 1
end do
!$omp end target parallel loop
end subroutine