xref: /llvm-project/flang/test/Lower/OpenMP/teams.f90 (revision bfeebda3b1cc1a05e435e94f54bf2d2a2570b4e2)
1! REQUIRES: openmp_runtime
2
3! RUN: %flang_fc1 -emit-hlfir %openmp_flags -fopenmp-version=52 %s -o - | FileCheck %s
4
5! CHECK-LABEL: func @_QPteams_simple
6subroutine teams_simple()
7  ! CHECK: omp.teams
8  !$omp teams
9  ! CHECK: fir.call
10  call f1()
11  ! CHECK: omp.terminator
12  !$omp end teams
13end subroutine teams_simple
14
15!===============================================================================
16! `num_teams` clause
17!===============================================================================
18
19! CHECK-LABEL: func @_QPteams_numteams
20subroutine teams_numteams(num_teams)
21  integer, intent(inout) :: num_teams
22
23  ! CHECK: omp.teams
24  ! CHECK-SAME: num_teams( to %{{.*}}: i32)
25  !$omp teams num_teams(4)
26  ! CHECK: fir.call
27  call f1()
28  ! CHECK: omp.terminator
29  !$omp end teams
30
31  ! CHECK: omp.teams
32  ! CHECK-SAME: num_teams( to %{{.*}}: i32)
33  !$omp teams num_teams(num_teams)
34  ! CHECK: fir.call
35  call f2()
36  ! CHECK: omp.terminator
37  !$omp end teams
38
39end subroutine teams_numteams
40
41!===============================================================================
42! `if` clause
43!===============================================================================
44
45! CHECK-LABEL: func @_QPteams_if
46subroutine teams_if(alpha)
47  integer, intent(in) :: alpha
48  logical :: condition
49
50  ! CHECK: omp.teams
51  ! CHECK-SAME: if(%{{.*}})
52  !$omp teams if(.false.)
53  ! CHECK: fir.call
54  call f1()
55  ! CHECK: omp.terminator
56  !$omp end teams
57
58  ! CHECK: omp.teams
59  ! CHECK-SAME: if(%{{.*}})
60  !$omp teams if(alpha .le. 0)
61  ! CHECK: fir.call
62  call f2()
63  ! CHECK: omp.terminator
64  !$omp end teams
65
66  ! CHECK: omp.teams
67  ! CHECK-SAME: if(%{{.*}})
68  !$omp teams if(condition)
69  ! CHECK: fir.call
70  call f3()
71  ! CHECK: omp.terminator
72  !$omp end teams
73end subroutine teams_if
74
75!===============================================================================
76! `thread_limit` clause
77!===============================================================================
78
79! CHECK-LABEL: func @_QPteams_threadlimit
80subroutine teams_threadlimit(thread_limit)
81  integer, intent(inout) :: thread_limit
82
83  ! CHECK: omp.teams
84  ! CHECK-SAME: thread_limit(%{{.*}}: i32)
85  !$omp teams thread_limit(4)
86  ! CHECK: fir.call
87  call f1()
88  ! CHECK: omp.terminator
89  !$omp end teams
90
91  ! CHECK: omp.teams
92  ! CHECK-SAME: thread_limit(%{{.*}}: i32)
93  !$omp teams thread_limit(thread_limit)
94  ! CHECK: fir.call
95  call f2()
96  ! CHECK: omp.terminator
97  !$omp end teams
98
99end subroutine teams_threadlimit
100
101!===============================================================================
102! `allocate` clause
103!===============================================================================
104
105! CHECK-LABEL: func @_QPteams_allocate
106subroutine teams_allocate()
107   use omp_lib
108   integer :: x
109   ! CHECK: omp.teams
110   ! CHECK-SAME: allocate(%{{.+}} : i64 -> %{{.+}} : !fir.ref<i32>)
111   !$omp teams allocate(omp_high_bw_mem_alloc: x) private(x)
112   ! CHECK: arith.addi
113   x = x + 12
114   ! CHECK: omp.terminator
115   !$omp end teams
116end subroutine teams_allocate
117