Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Lower / OpenMP / single.f90
blobd4139ce0fe43b10b3901fd4a8e19437da896ecba
1 !RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
2 !RUN: bbc -emit-fir -fopenmp %s -o - | FileCheck %s
4 !===============================================================================
5 ! Single construct
6 !===============================================================================
8 !CHECK-LABEL: func @_QPomp_single
9 !CHECK-SAME: (%[[x:.*]]: !fir.ref<i32> {fir.bindc_name = "x"})
10 subroutine omp_single(x)
11 integer, intent(inout) :: x
12 !CHECK: omp.parallel
13 !$omp parallel
14 !CHECK: omp.single
15 !$omp single
16 !CHECK: %[[xval:.*]] = fir.load %[[x]] : !fir.ref<i32>
17 !CHECK: %[[res:.*]] = arith.addi %[[xval]], %{{.*}} : i32
18 !CHECK: fir.store %[[res]] to %[[x]] : !fir.ref<i32>
19 x = x + 12
20 !CHECK: omp.terminator
21 !$omp end single
22 !CHECK: omp.terminator
23 !$omp end parallel
24 end subroutine omp_single
26 !===============================================================================
27 ! Single construct with nowait
28 !===============================================================================
30 !CHECK-LABEL: func @_QPomp_single_nowait
31 !CHECK-SAME: (%[[x:.*]]: !fir.ref<i32> {fir.bindc_name = "x"})
32 subroutine omp_single_nowait(x)
33 integer, intent(inout) :: x
34 !CHECK: omp.parallel
35 !$omp parallel
36 !CHECK: omp.single nowait
37 !$omp single
38 !CHECK: %[[xval:.*]] = fir.load %[[x]] : !fir.ref<i32>
39 !CHECK: %[[res:.*]] = arith.addi %[[xval]], %{{.*}} : i32
40 !CHECK: fir.store %[[res]] to %[[x]] : !fir.ref<i32>
41 x = x + 12
42 !CHECK: omp.terminator
43 !$omp end single nowait
44 !CHECK: omp.terminator
45 !$omp end parallel
46 end subroutine omp_single_nowait
48 !===============================================================================
49 ! Single construct with allocate
50 !===============================================================================
52 !CHECK-LABEL: func @_QPsingle_allocate
53 subroutine single_allocate()
54 use omp_lib
55 integer :: x
56 !CHECK: omp.parallel {
57 !$omp parallel
58 !CHECK: omp.single allocate(%{{.+}} : i32 -> %{{.+}} : !fir.ref<i32>) {
59 !$omp single allocate(omp_high_bw_mem_alloc: x) private(x)
60 !CHECK: arith.addi
61 x = x + 12
62 !CHECK: omp.terminator
63 !$omp end single
64 !CHECK: omp.terminator
65 !$omp end parallel
66 end subroutine single_allocate
68 !===============================================================================
69 ! Single construct with private/firstprivate
70 !===============================================================================
72 ! CHECK-LABEL: func.func @_QPsingle_privatization(
73 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<f32> {fir.bindc_name = "x"},
74 ! CHECK-SAME: %[[VAL_1:.*]]: !fir.ref<f64> {fir.bindc_name = "y"}) {
75 ! CHECK: %[[VAL_2:.*]] = fir.alloca f32 {bindc_name = "x", pinned, uniq_name = "_QFsingle_privatizationEx"}
76 ! CHECK: %[[VAL_3:.*]] = fir.alloca f64 {bindc_name = "y", pinned, uniq_name = "_QFsingle_privatizationEy"}
77 ! CHECK: omp.single {
78 ! CHECK: %[[VAL_4:.*]] = fir.load %[[VAL_1]] : !fir.ref<f64>
79 ! CHECK: fir.store %[[VAL_4]] to %[[VAL_3]] : !fir.ref<f64>
80 ! CHECK: fir.call @_QPbar(%[[VAL_2]], %[[VAL_3]]) {{.*}}: (!fir.ref<f32>, !fir.ref<f64>) -> ()
81 ! CHECK: omp.terminator
82 ! CHECK: }
83 ! CHECK: return
84 ! CHECK: }
86 subroutine single_privatization(x, y)
87 real :: x
88 real(8) :: y
90 !$omp single private(x) firstprivate(y)
91 call bar(x, y)
92 !$omp end single
93 end subroutine
95 ! CHECK-LABEL: func.func @_QPsingle_privatization2(
96 ! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<f32> {fir.bindc_name = "x"},
97 ! CHECK-SAME: %[[VAL_1:.*]]: !fir.ref<f64> {fir.bindc_name = "y"}) {
98 ! CHECK: omp.parallel {
99 ! CHECK: %[[VAL_2:.*]] = fir.alloca f32 {bindc_name = "x", pinned, uniq_name = "_QFsingle_privatization2Ex"}
100 ! CHECK: %[[VAL_3:.*]] = fir.alloca f64 {bindc_name = "y", pinned, uniq_name = "_QFsingle_privatization2Ey"}
101 ! CHECK: omp.single {
102 ! CHECK: %[[VAL_4:.*]] = fir.load %[[VAL_1]] : !fir.ref<f64>
103 ! CHECK: fir.store %[[VAL_4]] to %[[VAL_3]] : !fir.ref<f64>
104 ! CHECK: fir.call @_QPbar(%[[VAL_2]], %[[VAL_3]]) {{.*}}: (!fir.ref<f32>, !fir.ref<f64>) -> ()
105 ! CHECK: omp.terminator
106 ! CHECK: }
107 ! CHECK: omp.terminator
108 ! CHECK: }
109 ! CHECK: return
110 ! CHECK: }
112 subroutine single_privatization2(x, y)
113 real :: x
114 real(8) :: y
116 !$omp parallel
117 !$omp single private(x) firstprivate(y)
118 call bar(x, y)
119 !$omp end single
120 !$omp end parallel
121 end subroutine