Skip to content

Commit 6005fdf

Browse files
Fix for two instances of multiple privatization
Privatization was happening more than once in two different situations. 1. If private clauses are part of a combined construct then privatization only needs to happen once. In the code base currently this happens only for parallel_do. Issue is fixed by not performing privatization while creating the parallel op. 2. Loop index variables are privatized by default if they occur in a parallel region. They were further privatized if part of a private clause. Fixed the issue by not performing privatization if it is part of a private clause. Note: Also switching to American spelling for privatize.
1 parent d97d0e9 commit 6005fdf

File tree

2 files changed

+63
-9
lines changed

2 files changed

+63
-9
lines changed

flang/lib/Lower/OpenMP.cpp

Lines changed: 16 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ getDesignatorNameIfDataRef(const Fortran::parser::Designator &designator) {
2929
return dataRef ? std::get_if<Fortran::parser::Name>(&dataRef->u) : nullptr;
3030
}
3131

32-
static void privatiseVars(Fortran::lower::AbstractConverter &converter,
32+
static void privatizeVars(Fortran::lower::AbstractConverter &converter,
3333
const Fortran::parser::OmpClauseList &opClauseList) {
3434
auto &firOpBuilder = converter.getFirOpBuilder();
3535
Fortran::semantics::Symbol *sym = nullptr;
@@ -50,9 +50,13 @@ static void privatiseVars(Fortran::lower::AbstractConverter &converter,
5050
},
5151
[&](const Fortran::parser::Name &name) { sym = name.symbol; }},
5252
ompObject.u);
53-
[[maybe_unused]] bool success =
54-
converter.createHostAssociateVarClone(*sym);
55-
assert(success && "Privatisation failed due to existing binding");
53+
// Privatization for symbols which are pre-determined (like loop index
54+
// variables) happen separately, for everything else privatize here
55+
if (!sym->test(Fortran::semantics::Symbol::Flag::OmpPreDetermined)) {
56+
[[maybe_unused]] bool success =
57+
converter.createHostAssociateVarClone(*sym);
58+
assert(success && "Privatization failed due to existing binding");
59+
}
5660
}
5761
}
5862
}
@@ -128,7 +132,7 @@ static void createBodyOfOp(
128132
// Reset the insertion point to the start of the first block.
129133
firOpBuilder.setInsertionPointToStart(&block);
130134
if (clauses)
131-
privatiseVars(converter, *clauses);
135+
privatizeVars(converter, *clauses);
132136
}
133137

134138
static void genOMP(Fortran::lower::AbstractConverter &converter,
@@ -199,7 +203,7 @@ genOMP(Fortran::lower::AbstractConverter &converter,
199203
standaloneConstruct.u);
200204
}
201205

202-
template <typename Directive>
206+
template <typename Directive, bool isCombined>
203207
static void createParallelOp(Fortran::lower::AbstractConverter &converter,
204208
Fortran::lower::pft::Evaluation &eval,
205209
const Directive &directive) {
@@ -317,8 +321,11 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
317321
}
318322
}
319323

324+
// Avoid multiple privatization: If Parallel is part of a combined construct
325+
// then privatization will be performed later when the other part of the
326+
// combined construct is processed.
320327
createBodyOfOp<omp::ParallelOp>(parallelOp, converter, currentLocation,
321-
&opClauseList);
328+
isCombined ? nullptr : &opClauseList);
322329
}
323330

324331
static void
@@ -331,7 +338,7 @@ genOMP(Fortran::lower::AbstractConverter &converter,
331338
std::get<Fortran::parser::OmpBlockDirective>(beginBlockDirective.t);
332339

333340
if (blockDirective.v == llvm::omp::OMPD_parallel) {
334-
createParallelOp<Fortran::parser::OmpBeginBlockDirective>(
341+
createParallelOp<Fortran::parser::OmpBeginBlockDirective, false>(
335342
converter, eval,
336343
std::get<Fortran::parser::OmpBeginBlockDirective>(blockConstruct.t));
337344
} else if (blockDirective.v == llvm::omp::OMPD_master) {
@@ -436,7 +443,7 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
436443
std::get<Fortran::parser::OmpLoopDirective>(
437444
std::get<Fortran::parser::OmpBeginLoopDirective>(loopConstruct.t).t)
438445
.v) {
439-
createParallelOp<Fortran::parser::OmpBeginLoopDirective>(
446+
createParallelOp<Fortran::parser::OmpBeginLoopDirective, true>(
440447
converter, eval,
441448
std::get<Fortran::parser::OmpBeginLoopDirective>(loopConstruct.t));
442449
} else {
Lines changed: 47 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,47 @@
1+
! This test checks a few bug fixes in the PRIVATE clause lowering
2+
3+
! RUN: bbc -fopenmp -emit-fir %s -o - | \
4+
! RUN: FileCheck %s
5+
6+
! CHECK-LABEL: multiple_private_fix
7+
! CHECK: %[[VAL_0:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFmultiple_private_fixEi"}
8+
! CHECK: %[[VAL_1:.*]] = fir.alloca i32 {bindc_name = "j", uniq_name = "_QFmultiple_private_fixEj"}
9+
! CHECK: %[[VAL_2:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFmultiple_private_fixEx"}
10+
! CHECK: omp.parallel {
11+
! CHECK: %[[VAL_0:.*]] = fir.alloca i32 {bindc_name = "j", pinned}
12+
! CHECK: %[[VAL_1:.*]] = fir.alloca i32 {bindc_name = "x", pinned, uniq_name = "_QFmultiple_private_fixEx"}
13+
! CHECK: %[[VAL_2:.*]] = constant 1 : i32
14+
! CHECK: %[[VAL_3:.*]] = fir.load %[[VAL_4:.*]] : !fir.ref<i32>
15+
! CHECK: %[[VAL_5:.*]] = constant 1 : i32
16+
! CHECK: omp.wsloop (%[[VAL_6:.*]]) : i32 = (%[[VAL_2]]) to (%[[VAL_3]]) step (%[[VAL_5]]) inclusive {
17+
! CHECK: %[[VAL_7:.*]] = constant 1 : i32
18+
! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_7]] : (i32) -> index
19+
! CHECK: %[[VAL_9:.*]] = fir.load %[[VAL_4]] : !fir.ref<i32>
20+
! CHECK: %[[VAL_10:.*]] = fir.convert %[[VAL_9]] : (i32) -> index
21+
! CHECK: %[[VAL_11:.*]] = constant 1 : index
22+
! CHECK: %[[VAL_12:.*]] = fir.do_loop %[[VAL_13:.*]] = %[[VAL_8]] to %[[VAL_10]] step %[[VAL_11]] -> index {
23+
! CHECK: %[[VAL_14:.*]] = fir.convert %[[VAL_13]] : (index) -> i32
24+
! CHECK: fir.store %[[VAL_14]] to %[[VAL_0]] : !fir.ref<i32>
25+
! CHECK: %[[VAL_15:.*]] = fir.load %[[VAL_0]] : !fir.ref<i32>
26+
! CHECK: %[[VAL_16:.*]] = addi %[[VAL_6]], %[[VAL_15]] : i32
27+
! CHECK: fir.store %[[VAL_16]] to %[[VAL_1]] : !fir.ref<i32>
28+
! CHECK: %[[VAL_17:.*]] = addi %[[VAL_13]], %[[VAL_11]] : index
29+
! CHECK: fir.result %[[VAL_17]] : index
30+
! CHECK: }
31+
! CHECK: %[[VAL_18:.*]] = fir.convert %[[VAL_19:.*]] : (index) -> i32
32+
! CHECK: fir.store %[[VAL_18]] to %[[VAL_0]] : !fir.ref<i32>
33+
! CHECK: omp.yield
34+
! CHECK: }
35+
! CHECK: omp.terminator
36+
! CHECK: }
37+
! CHECK: return
38+
subroutine multiple_private_fix(gama)
39+
integer :: i, j, x, gama
40+
!$OMP PARALLEL DO PRIVATE(j,x)
41+
do i = 1, gama
42+
do j = 1, gama
43+
x = i + j
44+
end do
45+
end do
46+
!$OMP END PARALLEL DO
47+
end subroutine

0 commit comments

Comments
 (0)