Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / OpenMP / task.f90
blob810e3b521a26b0fb93708caab9b19630a495c857
1 !RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
3 !CHECK-LABEL: func @_QPomp_task_simple() {
4 subroutine omp_task_simple
5 !CHECK: omp.task {
6 !$omp task
7 !CHECK: fir.call @_QPfoo() {{.*}}: () -> ()
8 call foo()
9 !CHECK: omp.terminator
10 !$omp end task
11 end subroutine omp_task_simple
13 !===============================================================================
14 ! `if` clause
15 !===============================================================================
17 !CHECK-LABEL: func @_QPomp_task_if(%{{.+}}) {
18 subroutine omp_task_if(bar)
19 logical, intent(inout) :: bar
20 !CHECK: omp.task if(%{{.+}}) {
21 !$omp task if(bar)
22 !CHECK: fir.call @_QPfoo() {{.*}}: () -> ()
23 call foo()
24 !CHECK: omp.terminator
25 !$omp end task
26 end subroutine omp_task_if
28 !===============================================================================
29 ! `final` clause
30 !===============================================================================
32 !CHECK-LABEL: func @_QPomp_task_final(%{{.+}}) {
33 subroutine omp_task_final(bar)
34 logical, intent(inout) :: bar
35 !CHECK: omp.task final(%{{.+}}) {
36 !$omp task final(bar)
37 !CHECK: fir.call @_QPfoo() {{.*}}: () -> ()
38 call foo()
39 !CHECK: omp.terminator
40 !$omp end task
41 end subroutine omp_task_final
43 !===============================================================================
44 ! `untied` clause
45 !===============================================================================
47 !CHECK-LABEL: func @_QPomp_task_untied() {
48 subroutine omp_task_untied()
49 !CHECK: omp.task untied {
50 !$omp task untied
51 !CHECK: fir.call @_QPfoo() {{.*}}: () -> ()
52 call foo()
53 !CHECK: omp.terminator
54 !$omp end task
55 end subroutine omp_task_untied
57 !===============================================================================
58 ! `mergeable` clause
59 !===============================================================================
61 !CHECK-LABEL: func @_QPomp_task_mergeable() {
62 subroutine omp_task_mergeable()
63 !CHECK: omp.task mergeable {
64 !$omp task mergeable
65 !CHECK: fir.call @_QPfoo() {{.*}}: () -> ()
66 call foo()
67 !CHECK: omp.terminator
68 !$omp end task
69 end subroutine omp_task_mergeable
71 !===============================================================================
72 ! `priority` clause
73 !===============================================================================
75 !CHECK-LABEL: func @_QPomp_task_priority(%{{.+}}) {
76 subroutine omp_task_priority(bar)
77 integer, intent(inout) :: bar
78 !CHECK: omp.task priority(%{{.+}}) {
79 !$omp task priority(bar)
80 !CHECK: fir.call @_QPfoo() {{.*}}: () -> ()
81 call foo()
82 !CHECK: omp.terminator
83 !$omp end task
84 end subroutine omp_task_priority
86 !===============================================================================
87 ! `allocate` clause
88 !===============================================================================
90 !CHECK-LABEL: func @_QPtask_allocate
91 subroutine task_allocate()
92 use omp_lib
93 integer :: x
94 !CHECK: omp.task allocate(%{{.+}} : i32 -> %{{.+}} : !fir.ref<i32>) {
95 !$omp task allocate(omp_high_bw_mem_alloc: x) private(x)
96 !CHECK: arith.addi
97 x = x + 12
98 !CHECK: omp.terminator
99 !$omp end task
100 end subroutine task_allocate
102 !===============================================================================
103 ! `private` clause
104 !===============================================================================
105 !CHECK-LABEL: func @_QPtask_private
106 subroutine task_private
107 type mytype
108 integer :: x
109 end type mytype
111 !CHECK: %[[int_var:.+]] = fir.alloca i32
112 !CHECK: %[[mytype_var:.+]] = fir.alloca !fir.type<_QFtask_privateTmytype{x:i32}>
113 integer :: int_var
114 type(mytype) :: mytype_var
116 !CHECK: fir.call @_QPbar(%[[int_var]], %[[mytype_var]]) {{.*}}: (!fir.ref<i32>, !fir.ref<!fir.type<_QFtask_privateTmytype{x:i32}>>) -> ()
117 call bar(int_var, mytype_var)
119 !CHECK: omp.task {
120 !$omp task private(int_var, mytype_var)
121 !CHECK: %[[int_var_private:.+]] = fir.alloca i32
122 !CHECK: %[[mytype_var_private:.+]] = fir.alloca !fir.type<_QFtask_privateTmytype{x:i32}>
124 !CHECK: fir.call @_QPbar(%[[int_var_private]], %[[mytype_var_private]]) {{.*}}: (!fir.ref<i32>, !fir.ref<!fir.type<_QFtask_privateTmytype{x:i32}>>) -> ()
125 call bar(int_var, mytype_var)
126 !CHECK: omp.terminator
127 !$omp end task
128 end subroutine task_private
130 !===============================================================================
131 ! `firstprivate` clause
132 !===============================================================================
133 !CHECK-LABEL: func @_QPtask_firstprivate
134 subroutine task_firstprivate
135 type mytype
136 integer :: x
137 end type mytype
139 !CHECK: %[[int_var:.+]] = fir.alloca i32
140 !CHECK: %[[mytype_var:.+]] = fir.alloca !fir.type<_QFtask_firstprivateTmytype{x:i32}>
141 integer :: int_var
142 type(mytype) :: mytype_var
144 !CHECK: fir.call @_QPbaz(%[[int_var]], %[[mytype_var]]) {{.*}}: (!fir.ref<i32>, !fir.ref<!fir.type<_QFtask_firstprivateTmytype{x:i32}>>) -> ()
145 call baz(int_var, mytype_var)
147 !CHECK: omp.task {
148 !$omp task firstprivate(int_var, mytype_var)
149 !CHECK: %[[int_var_firstprivate:.+]] = fir.alloca i32
150 !CHECK: %[[int_var_load:.+]] = fir.load %[[int_var]] : !fir.ref<i32>
151 !CHECK: fir.store %[[int_var_load]] to %[[int_var_firstprivate]] : !fir.ref<i32>
152 !CHECK: %[[mytype_var_firstprivate:.+]] = fir.alloca !fir.type<_QFtask_firstprivateTmytype{x:i32}>
153 !CHECK: %[[mytype_var_load:.+]] = fir.load %[[mytype_var]] : !fir.ref<!fir.type<_QFtask_firstprivateTmytype{x:i32}>>
154 !CHECK: fir.store %[[mytype_var_load]] to %[[mytype_var_firstprivate]]
155 !CHECK: fir.call @_QPbaz(%[[int_var_firstprivate]], %[[mytype_var_firstprivate]]) {{.*}}: (!fir.ref<i32>, !fir.ref<!fir.type<_QFtask_firstprivateTmytype{x:i32}>>) -> ()
156 call baz(int_var, mytype_var)
157 !CHECK: omp.terminator
158 !$omp end task
159 end subroutine task_firstprivate
161 !===============================================================================
162 ! Multiple clauses
163 !===============================================================================
165 !CHECK-LABEL: func @_QPtask_multiple_clauses
166 subroutine task_multiple_clauses()
167 use omp_lib
169 !CHECK: %[[x:.+]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFtask_multiple_clausesEx"}
170 !CHECK: %[[y:.+]] = fir.alloca i32 {bindc_name = "y", uniq_name = "_QFtask_multiple_clausesEy"}
171 !CHECK: %[[z:.+]] = fir.alloca i32 {bindc_name = "z", uniq_name = "_QFtask_multiple_clausesEz"}
172 integer :: x, y, z
173 logical :: buzz
175 !CHECK: omp.task if(%{{.+}}) final(%{{.+}}) untied mergeable priority(%{{.+}}) allocate(%{{.+}} : i32 -> %{{.+}} : !fir.ref<i32>) {
176 !$omp task if(buzz) final(buzz) untied mergeable priority(z) allocate(omp_high_bw_mem_alloc: x) private(x) firstprivate(y)
178 !CHECK: %[[x_priv:.+]] = fir.alloca i32
179 !CHECK: %[[y_priv:.+]] = fir.alloca i32
180 !CHECK: %[[y_load:.+]] = fir.load %[[y]] : !fir.ref<i32>
181 !CHECK: fir.store %[[y_load]] to %[[y_priv]] : !fir.ref<i32>
183 !CHECK: arith.addi
184 x = x + 12
185 !CHECK: arith.subi
186 y = y - 12
188 !CHECK: omp.terminator
189 !$omp end task
190 end subroutine task_multiple_clauses