xref: /llvm-project/flang/test/Lower/OpenMP/wsloop-reduction-max-byref.f90 (revision 937cbce14c9aa956342a9c818c26a8a557802843)
1! RUN: bbc -emit-hlfir -fopenmp --force-byref-reduction -o - %s 2>&1 | FileCheck %s
2! RUN: %flang_fc1 -emit-hlfir -fopenmp -mmlir --force-byref-reduction -o - %s 2>&1 | FileCheck %s
3
4! NOTE: Assertions have been autogenerated by utils/generate-test-checks.py
5
6!CHECK-LABEL: omp.declare_reduction @max_byref_f32 : !fir.ref<f32>
7!CHECK-SAME: alloc {
8!CHECK:   %[[REF:.*]] = fir.alloca f32
9!CHECK:   omp.yield(%[[REF]] : !fir.ref<f32>)
10!CHECK-LABEL: } init {
11!CHECK:   %[[MINIMUM_VAL:.*]] = arith.constant -3.40282347E+38 : f32
12!CHECK:   fir.store %[[MINIMUM_VAL]] to %[[ALLOC:.*]] : !fir.ref<f32>
13!CHECK:   omp.yield(%[[ALLOC]] : !fir.ref<f32>)
14!CHECK: combiner
15!CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<f32>, %[[ARG1:.*]]: !fir.ref<f32>):
16!CHECK:   %[[LD0:.*]] = fir.load %[[ARG0]] : !fir.ref<f32>
17!CHECK:   %[[LD1:.*]] = fir.load %[[ARG1]] : !fir.ref<f32>
18!CHECK:   %[[RES:.*]] = arith.maxnumf %[[LD0]], %[[LD1]] {{.*}}: f32
19!CHECK:   fir.store %[[RES]] to %[[ARG0]] : !fir.ref<f32>
20!CHECK:   omp.yield(%[[ARG0]] : !fir.ref<f32>)
21
22!CHECK-LABEL: omp.declare_reduction @max_byref_i32 : !fir.ref<i32>
23!CHECK-SAME: alloc {
24!CHECK:   %[[REF:.*]] = fir.alloca i32
25!CHECK:   omp.yield(%[[REF]] : !fir.ref<i32>)
26!CHECK-LABEL: } init {
27!CHECK:   %[[MINIMUM_VAL:.*]] = arith.constant -2147483648 : i32
28!CHECK:   fir.store %[[MINIMUM_VAL]] to %[[ALLOC:.*]] : !fir.ref<i32>
29!CHECK:   omp.yield(%[[ALLOC]] : !fir.ref<i32>)
30!CHECK: combiner
31!CHECK: ^bb0(%[[ARG0:.*]]: !fir.ref<i32>, %[[ARG1:.*]]: !fir.ref<i32>):
32!CHECK:   %[[LD0:.*]] = fir.load %[[ARG0]] : !fir.ref<i32>
33!CHECK:   %[[LD1:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
34!CHECK:   %[[RES:.*]] = arith.maxsi %[[LD0]], %[[LD1]] : i32
35!CHECK:   fir.store %[[RES]] to %[[ARG0]] : !fir.ref<i32>
36!CHECK:   omp.yield(%[[ARG0]] : !fir.ref<i32>)
37
38! CHECK-LABEL:   func.func @_QPreduction_max_int(
39! CHECK-SAME:                                    %[[VAL_0:.*]]: !fir.box<!fir.array<?xi32>> {fir.bindc_name = "y"}) {
40! CHECK:           %[[VAL_1:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFreduction_max_intEi"}
41! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]] {uniq_name = "_QFreduction_max_intEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
42! CHECK:           %[[VAL_3:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFreduction_max_intEx"}
43! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_3]] {uniq_name = "_QFreduction_max_intEx"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
44! CHECK:           %[[VAL_5:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFreduction_max_intEy"} : (!fir.box<!fir.array<?xi32>>, !fir.dscope) -> (!fir.box<!fir.array<?xi32>>, !fir.box<!fir.array<?xi32>>)
45! CHECK:           %[[VAL_6:.*]] = arith.constant 0 : i32
46! CHECK:           hlfir.assign %[[VAL_6]] to %[[VAL_4]]#0 : i32, !fir.ref<i32>
47! CHECK:           omp.parallel {
48! CHECK:             %[[VAL_7:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}}
49! CHECK:             %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_7]] {uniq_name = "_QFreduction_max_intEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
50! CHECK:             %[[VAL_9:.*]] = arith.constant 1 : i32
51! CHECK:             %[[VAL_10:.*]] = arith.constant 100 : i32
52! CHECK:             %[[VAL_11:.*]] = arith.constant 1 : i32
53! CHECK:             omp.wsloop reduction(byref @max_byref_i32 %[[VAL_4]]#0 -> %[[VAL_12:.*]] : !fir.ref<i32>) {
54! CHECK-NEXT:          omp.loop_nest (%[[VAL_13:.*]]) : i32 = (%[[VAL_9]]) to (%[[VAL_10]]) inclusive step (%[[VAL_11]]) {
55! CHECK:                 %[[VAL_14:.*]]:2 = hlfir.declare %[[VAL_12]] {uniq_name = "_QFreduction_max_intEx"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
56! CHECK:                 fir.store %[[VAL_13]] to %[[VAL_8]]#1 : !fir.ref<i32>
57! CHECK:                 %[[VAL_15:.*]] = fir.load %[[VAL_8]]#0 : !fir.ref<i32>
58! CHECK:                 %[[VAL_16:.*]] = fir.convert %[[VAL_15]] : (i32) -> i64
59! CHECK:                 %[[VAL_17:.*]] = hlfir.designate %[[VAL_5]]#0 (%[[VAL_16]])  : (!fir.box<!fir.array<?xi32>>, i64) -> !fir.ref<i32>
60! CHECK:                 %[[VAL_18:.*]] = fir.load %[[VAL_14]]#0 : !fir.ref<i32>
61! CHECK:                 %[[VAL_19:.*]] = fir.load %[[VAL_17]] : !fir.ref<i32>
62! CHECK:                 %[[VAL_20:.*]] = arith.cmpi sgt, %[[VAL_18]], %[[VAL_19]] : i32
63! CHECK:                 %[[VAL_21:.*]] = arith.select %[[VAL_20]], %[[VAL_18]], %[[VAL_19]] : i32
64! CHECK:                 hlfir.assign %[[VAL_21]] to %[[VAL_14]]#0 : i32, !fir.ref<i32>
65! CHECK:                 omp.yield
66! CHECK:             omp.terminator
67
68! CHECK-LABEL:   func.func @_QPreduction_max_real(
69! CHECK-SAME:                                     %[[VAL_0:.*]]: !fir.box<!fir.array<?xf32>> {fir.bindc_name = "y"}) {
70! CHECK:           %[[VAL_1:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFreduction_max_realEi"}
71! CHECK:           %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_1]] {uniq_name = "_QFreduction_max_realEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
72! CHECK:           %[[VAL_3:.*]] = fir.alloca f32 {bindc_name = "x", uniq_name = "_QFreduction_max_realEx"}
73! CHECK:           %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_3]] {uniq_name = "_QFreduction_max_realEx"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
74! CHECK:           %[[VAL_5:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFreduction_max_realEy"} : (!fir.box<!fir.array<?xf32>>, !fir.dscope) -> (!fir.box<!fir.array<?xf32>>, !fir.box<!fir.array<?xf32>>)
75! CHECK:           %[[VAL_6:.*]] = arith.constant 0.000000e+00 : f32
76! CHECK:           hlfir.assign %[[VAL_6]] to %[[VAL_4]]#0 : f32, !fir.ref<f32>
77! CHECK:           omp.parallel {
78! CHECK:             %[[VAL_7:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}}
79! CHECK:             %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_7]] {uniq_name = "_QFreduction_max_realEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
80! CHECK:             %[[VAL_9:.*]] = arith.constant 1 : i32
81! CHECK:             %[[VAL_10:.*]] = arith.constant 100 : i32
82! CHECK:             %[[VAL_11:.*]] = arith.constant 1 : i32
83! CHECK:             omp.wsloop reduction(byref @max_byref_f32 %[[VAL_4]]#0 -> %[[VAL_12:.*]] : !fir.ref<f32>) {
84! CHECK-NEXT:          omp.loop_nest (%[[VAL_13:.*]]) : i32 = (%[[VAL_9]]) to (%[[VAL_10]]) inclusive step (%[[VAL_11]]) {
85! CHECK:                 %[[VAL_14:.*]]:2 = hlfir.declare %[[VAL_12]] {uniq_name = "_QFreduction_max_realEx"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
86! CHECK:                 fir.store %[[VAL_13]] to %[[VAL_8]]#1 : !fir.ref<i32>
87! CHECK:                 %[[VAL_15:.*]] = fir.load %[[VAL_8]]#0 : !fir.ref<i32>
88! CHECK:                 %[[VAL_16:.*]] = fir.convert %[[VAL_15]] : (i32) -> i64
89! CHECK:                 %[[VAL_17:.*]] = hlfir.designate %[[VAL_5]]#0 (%[[VAL_16]])  : (!fir.box<!fir.array<?xf32>>, i64) -> !fir.ref<f32>
90! CHECK:                 %[[VAL_18:.*]] = fir.load %[[VAL_17]] : !fir.ref<f32>
91! CHECK:                 %[[VAL_19:.*]] = fir.load %[[VAL_14]]#0 : !fir.ref<f32>
92! CHECK:                 %[[VAL_20:.*]] = arith.cmpf ogt, %[[VAL_18]], %[[VAL_19]] fastmath<contract> : f32
93! CHECK:                 %[[VAL_21:.*]] = arith.select %[[VAL_20]], %[[VAL_18]], %[[VAL_19]] : f32
94! CHECK:                 hlfir.assign %[[VAL_21]] to %[[VAL_14]]#0 : f32, !fir.ref<f32>
95! CHECK:                 omp.yield
96! CHECK:             omp.terminator
97! CHECK:           omp.parallel {
98! CHECK:             %[[VAL_30:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}}
99! CHECK:             %[[VAL_31:.*]]:2 = hlfir.declare %[[VAL_30]] {uniq_name = "_QFreduction_max_realEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
100! CHECK:             %[[VAL_32:.*]] = arith.constant 1 : i32
101! CHECK:             %[[VAL_33:.*]] = arith.constant 100 : i32
102! CHECK:             %[[VAL_34:.*]] = arith.constant 1 : i32
103! CHECK:             omp.wsloop reduction(byref @max_byref_f32 %[[VAL_4]]#0 -> %[[VAL_35:.*]] : !fir.ref<f32>) {
104! CHECK-NEXT:          omp.loop_nest (%[[VAL_36:.*]]) : i32 = (%[[VAL_32]]) to (%[[VAL_33]]) inclusive step (%[[VAL_34]]) {
105! CHECK:                 %[[VAL_37:.*]]:2 = hlfir.declare %[[VAL_35]] {uniq_name = "_QFreduction_max_realEx"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
106! CHECK:                 fir.store %[[VAL_36]] to %[[VAL_31]]#1 : !fir.ref<i32>
107! CHECK:                 %[[VAL_38:.*]] = fir.load %[[VAL_31]]#0 : !fir.ref<i32>
108! CHECK:                 %[[VAL_39:.*]] = fir.convert %[[VAL_38]] : (i32) -> i64
109! CHECK:                 %[[VAL_40:.*]] = hlfir.designate %[[VAL_5]]#0 (%[[VAL_39]])  : (!fir.box<!fir.array<?xf32>>, i64) -> !fir.ref<f32>
110! CHECK:                 %[[VAL_41:.*]] = fir.load %[[VAL_40]] : !fir.ref<f32>
111! CHECK:                 %[[VAL_42:.*]] = fir.load %[[VAL_37]]#0 : !fir.ref<f32>
112! CHECK:                 %[[VAL_43:.*]] = arith.cmpf ogt, %[[VAL_41]], %[[VAL_42]] fastmath<contract> : f32
113! CHECK:                 fir.if %[[VAL_43]] {
114! CHECK:                   %[[VAL_44:.*]] = fir.load %[[VAL_31]]#0 : !fir.ref<i32>
115! CHECK:                   %[[VAL_45:.*]] = fir.convert %[[VAL_44]] : (i32) -> i64
116! CHECK:                   %[[VAL_46:.*]] = hlfir.designate %[[VAL_5]]#0 (%[[VAL_45]])  : (!fir.box<!fir.array<?xf32>>, i64) -> !fir.ref<f32>
117! CHECK:                   %[[VAL_47:.*]] = fir.load %[[VAL_46]] : !fir.ref<f32>
118! CHECK:                   hlfir.assign %[[VAL_47]] to %[[VAL_37]]#0 : f32, !fir.ref<f32>
119! CHECK:                 }
120! CHECK:                 omp.yield
121! CHECK:             omp.terminator
122
123
124
125subroutine reduction_max_int(y)
126  integer :: x, y(:)
127  x = 0
128  !$omp parallel
129  !$omp do reduction(max:x)
130  do i=1, 100
131    x = max(x, y(i))
132  end do
133  !$omp end do
134  !$omp end parallel
135  print *, x
136end subroutine
137
138subroutine reduction_max_real(y)
139  real :: x, y(:)
140  x = 0.0
141  !$omp parallel
142  !$omp do reduction(max:x)
143  do i=1, 100
144    x = max(y(i), x)
145  end do
146  !$omp end do
147  !$omp end parallel
148  print *, x
149
150  !$omp parallel
151  !$omp do reduction(max:x)
152  do i=1, 100
153    if (y(i) .gt. x) x = y(i)
154  end do
155  !$omp end do
156  !$omp end parallel
157  print *, x
158end subroutine
159