Skip to content

Commit 7a3609c

Browse files
kiranchandramohanjeanPerier
authored andcommitted
Implementation of firstprivate transformation
The firstprivate transformation does privatisation and then copies the value of the original variable to the privatised variable. This commit handles the basic types.
1 parent 5e3c7fd commit 7a3609c

File tree

5 files changed

+102
-78
lines changed

5 files changed

+102
-78
lines changed

flang/include/flang/Lower/AbstractConverter.h

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -92,6 +92,8 @@ class AbstractConverter {
9292
virtual bool
9393
createHostAssociateVarClone(const Fortran::semantics::Symbol &sym) = 0;
9494

95+
virtual void copyHostAssociateVar(const Fortran::semantics::Symbol &sym) = 0;
96+
9597
//===--------------------------------------------------------------------===//
9698
// Expressions
9799
//===--------------------------------------------------------------------===//

flang/lib/Lower/Bridge.cpp

Lines changed: 40 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -329,30 +329,23 @@ class FirConverter : public Fortran::lower::AbstractConverter {
329329
bool createHostAssociateVarClone(
330330
const Fortran::semantics::Symbol &sym) override final {
331331
auto loc = genLocation(sym.name());
332+
mlir::Type symType = genType(sym);
332333
const auto *details = sym.detailsIf<Fortran::semantics::HostAssocDetails>();
333334
assert(details != nullptr && "No host-association found");
334335
const Fortran::semantics::Symbol &hsym = details->symbol();
335336
Fortran::lower::SymbolBox hsb = lookupSymbol(hsym);
336337

337338
auto allocate = [&](llvm::ArrayRef<mlir::Value> shape,
338339
llvm::ArrayRef<mlir::Value> typeParams) -> mlir::Value {
339-
mlir::Type symType = genType(sym);
340-
return builder->allocateLocal(
340+
auto allocVal = builder->allocateLocal(
341341
loc, symType, mangleName(sym), toStringRef(sym.GetUltimate().name()),
342342
/*pinned=*/true, shape, typeParams,
343343
sym.GetUltimate().attrs().test(Fortran::semantics::Attr::TARGET));
344-
};
345-
346-
auto getExtendedValue = [&](Fortran::lower::SymbolBox sb) {
347-
return sb.match(
348-
[&](const Fortran::lower::SymbolBox::PointerOrAllocatable &box) {
349-
return fir::factory::genMutableBoxRead(*builder, loc, box);
350-
},
351-
[&sb](auto &) { return sb.toExtendedValue(); });
344+
return allocVal;
352345
};
353346

354347
fir::ExtendedValue hexv = getExtendedValue(hsb);
355-
auto exval = hexv.match(
348+
auto exv = hexv.match(
356349
[&](const fir::BoxValue &box) -> fir::ExtendedValue {
357350
const auto *type = sym.GetType();
358351
if (type && type->IsPolymorphic())
@@ -380,7 +373,33 @@ class FirConverter : public Fortran::lower::AbstractConverter {
380373
fir::getTypeParams(hexv));
381374
return fir::substBase(hexv, temp);
382375
});
383-
return bindSymbol(sym, exval);
376+
377+
return bindSymbol(sym, exv);
378+
}
379+
380+
void
381+
copyHostAssociateVar(const Fortran::semantics::Symbol &sym) override final {
382+
Fortran::lower::SymbolBox sb = lookupSymbol(sym);
383+
fir::ExtendedValue exv = getExtendedValue(sb);
384+
385+
const auto *details = sym.detailsIf<Fortran::semantics::HostAssocDetails>();
386+
assert(details != nullptr && "No host-association found");
387+
const Fortran::semantics::Symbol &hsym = details->symbol();
388+
Fortran::lower::SymbolBox hsb = lookupSymbol(hsym);
389+
fir::ExtendedValue hexv = getExtendedValue(hsb);
390+
391+
auto loc = genLocation(sym.name());
392+
mlir::Type symType = genType(sym);
393+
if (auto seqTy = symType.dyn_cast<fir::SequenceType>()) {
394+
Fortran::lower::StatementContext stmtCtx;
395+
createSomeArrayAssignment(*this, exv, hexv, localSymbols, stmtCtx);
396+
stmtCtx.finalize();
397+
} else if (hsb.toExtendedValue().getBoxOf<fir::MutableBoxValue>()) {
398+
TODO(loc, "firstprivatisation of allocatable variables");
399+
} else {
400+
auto loadVal = builder->create<fir::LoadOp>(loc, getSymbolAddress(hsym));
401+
builder->create<fir::StoreOp>(loc, loadVal, getSymbolAddress(sym));
402+
}
384403
}
385404

386405
mlir::Location getCurrentLocation() override final { return toLocation(); }
@@ -471,6 +490,15 @@ class FirConverter : public Fortran::lower::AbstractConverter {
471490
return true;
472491
}
473492

493+
fir::ExtendedValue getExtendedValue(Fortran::lower::SymbolBox sb) {
494+
return sb.match(
495+
[&](const Fortran::lower::SymbolBox::PointerOrAllocatable &box) {
496+
return fir::factory::genMutableBoxRead(*builder,
497+
getCurrentLocation(), box);
498+
},
499+
[&sb](auto &) { return sb.toExtendedValue(); });
500+
}
501+
474502
mlir::Value createTemp(mlir::Location loc,
475503
const Fortran::semantics::Symbol &sym,
476504
llvm::ArrayRef<mlir::Value> shape = {}) {

flang/lib/Lower/OpenMP.cpp

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

32+
template <typename T>
33+
static void createPrivateVarSyms(Fortran::lower::AbstractConverter &converter,
34+
const T *clause) {
35+
Fortran::semantics::Symbol *sym = nullptr;
36+
const Fortran::parser::OmpObjectList &ompObjectList = clause->v;
37+
for (const auto &ompObject : ompObjectList.v) {
38+
std::visit(
39+
Fortran::common::visitors{
40+
[&](const Fortran::parser::Designator &designator) {
41+
if (const auto *name = getDesignatorNameIfDataRef(designator)) {
42+
sym = name->symbol;
43+
}
44+
},
45+
[&](const Fortran::parser::Name &name) { sym = name.symbol; }},
46+
ompObject.u);
47+
48+
// Privatization for symbols which are pre-determined (like loop index
49+
// variables) happen separately, for everything else privatize here
50+
if (!sym->test(Fortran::semantics::Symbol::Flag::OmpPreDetermined)) {
51+
[[maybe_unused]] bool success = converter.createHostAssociateVarClone(*sym);
52+
assert(success && "Privatization failed due to existing binding");
53+
constexpr bool init =
54+
std::is_same_v<T, Fortran::parser::OmpClause::Firstprivate>;
55+
if (init)
56+
converter.copyHostAssociateVar(*sym);
57+
}
58+
}
59+
}
60+
3261
static void privatizeVars(Fortran::lower::AbstractConverter &converter,
3362
const Fortran::parser::OmpClauseList &opClauseList) {
3463
auto &firOpBuilder = converter.getFirOpBuilder();
35-
Fortran::semantics::Symbol *sym = nullptr;
3664
auto insPt = firOpBuilder.saveInsertionPoint();
3765
firOpBuilder.setInsertionPointToStart(firOpBuilder.getAllocaBlock());
3866
for (const auto &clause : opClauseList.v) {
3967
if (const auto &privateClause =
4068
std::get_if<Fortran::parser::OmpClause::Private>(&clause.u)) {
41-
const Fortran::parser::OmpObjectList &ompObjectList = privateClause->v;
42-
for (const auto &ompObject : ompObjectList.v) {
43-
std::visit(
44-
Fortran::common::visitors{
45-
[&](const Fortran::parser::Designator &designator) {
46-
if (const auto *name =
47-
getDesignatorNameIfDataRef(designator)) {
48-
sym = name->symbol;
49-
}
50-
},
51-
[&](const Fortran::parser::Name &name) { sym = name.symbol; }},
52-
ompObject.u);
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-
}
60-
}
69+
createPrivateVarSyms(converter, privateClause);
70+
} else if (const auto &firstPrivateClause =
71+
std::get_if<Fortran::parser::OmpClause::Firstprivate>(
72+
&clause.u)) {
73+
createPrivateVarSyms(converter, firstPrivateClause);
6174
}
6275
}
6376
firOpBuilder.restoreInsertionPoint(insPt);
@@ -229,12 +242,6 @@ static void createParallelOp(Fortran::lower::AbstractConverter &converter,
229242
&clause.u)) {
230243
numThreadsClauseOperand = fir::getBase(converter.genExprValue(
231244
*Fortran::semantics::GetExpr(numThreadsClause->v), stmtCtx));
232-
} else if (const auto &firstprivateClause =
233-
std::get_if<Fortran::parser::OmpClause::Firstprivate>(
234-
&clause.u)) {
235-
const Fortran::parser::OmpObjectList &ompObjectList =
236-
firstprivateClause->v;
237-
genObjectList(ompObjectList, converter, firstprivateClauseOperands);
238245
} else if (const auto &sharedClause =
239246
std::get_if<Fortran::parser::OmpClause::Shared>(&clause.u)) {
240247
const Fortran::parser::OmpObjectList &ompObjectList = sharedClause->v;
@@ -446,16 +453,6 @@ static void genOMP(Fortran::lower::AbstractConverter &converter,
446453
createParallelOp<Fortran::parser::OmpBeginLoopDirective, true>(
447454
converter, eval,
448455
std::get<Fortran::parser::OmpBeginLoopDirective>(loopConstruct.t));
449-
} else {
450-
for (const auto &clause : wsLoopOpClauseList.v) {
451-
if (const auto &firstPrivateClause =
452-
std::get_if<Fortran::parser::OmpClause::Firstprivate>(
453-
&clause.u)) {
454-
const Fortran::parser::OmpObjectList &ompObjectList =
455-
firstPrivateClause->v;
456-
genObjectList(ompObjectList, converter, firstPrivateClauseOperands);
457-
}
458-
}
459456
}
460457
for (const auto &clause : wsLoopOpClauseList.v) {
461458
if (const auto &lastPrivateClause =

flang/lib/Optimizer/Builder/Runtime/Character.cpp

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -112,7 +112,7 @@ mlir::Value fir::runtime::genCharCompare(fir::FirOpBuilder &builder,
112112
auto allocateIfNotInMemory = [&](mlir::Value base) -> mlir::Value {
113113
if (fir::isa_ref_type(base.getType()))
114114
return base;
115-
auto mem = builder.create<fir::AllocaOp>(loc, base.getType());
115+
auto mem = builder.create<fir::AllocaOp>(loc, base.getType(), /*pinned=*/false);
116116
builder.create<fir::StoreOp>(loc, base, mem);
117117
return mem;
118118
};

flang/test/Lower/OpenMP/omp-parallel-firstprivate-clause.f90

Lines changed: 25 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -3,39 +3,36 @@
33

44
! RUN: bbc -fopenmp -emit-fir %s -o - | \
55
! RUN: FileCheck %s --check-prefix=FIRDialect
6-
! RUN: bbc -fopenmp %s -o - | \
7-
! RUN: tco --disable-llvm --print-ir-after=fir-to-llvm-ir 2>&1 | \
8-
! RUN: FileCheck %s --check-prefix=LLVMIRDialect
96

10-
!FIRDialect: func @_QPfirstprivate_clause(%[[ARG1:.*]]: !fir.ref<i32>, %[[ARG2:.*]]: !fir.ref<!fir.array<10xi32>>) {
11-
!FIRDialect-DAG: %[[ALPHA:.*]] = fir.alloca i32 {{{.*}}uniq_name = "{{.*}}Ealpha"}
12-
!FIRDialect-DAG: %[[BETA:.*]] = fir.alloca i32 {{{.*}}uniq_name = "{{.*}}Ebeta"}
13-
!FIRDialect-DAG: %[[GAMA:.*]] = fir.alloca i32 {{{.*}}uniq_name = "{{.*}}Egama"}
14-
!FIRDialect-DAG: %[[ALPHA_ARRAY:.*]] = fir.alloca !fir.array<10xi32> {{{.*}}uniq_name = "{{.*}}Ealpha_array"}
15-
!FIRDialect: omp.parallel firstprivate(%[[ALPHA]] : !fir.ref<i32>, %[[BETA]] : !fir.ref<i32>, %[[GAMA]] : !fir.ref<i32>,
16-
!%[[ALPHA_ARRAY]] : !fir.ref<!fir.array<10xi32>>, %[[ARG1]] : !fir.ref<i32>, %[[ARG2]] : !fir.ref<!fir.array<10xi32>>)) {
17-
!FIRDialect: omp.terminator
18-
!FIRDialect: }
7+
!FIRDialect: func @_QPfirstprivate_clause(%[[ARG1:.*]]: !fir.ref<i32>, %[[ARG2:.*]]: !fir.ref<!fir.array<10xi32>>, %[[ARG3:.*]]: !fir.ref<!fir.box<!fir.heap<i32>>>) {
8+
!FIRDialect-DAG: omp.parallel
9+
!FIRDialect-DAG: %[[ARG1_PVT:.*]] = fir.alloca i32 {{{.*}}uniq_name = "{{.*}}Earg1"}
10+
!FIRDialect-DAG: %[[ARG1_PVT_LOAD:.*]] = fir.load %[[ARG1]] : !fir.ref<i32>
11+
!FIRDialect-DAG: fir.store %[[ARG1_PVT_LOAD]] to %[[ARG1_PVT]] : !fir.ref<i32>
12+
!FIRDialect-DAG: %[[ARG2_PRIVATE:.*]] = fir.alloca !fir.array<10xi32> {{{.*}}uniq_name = "{{.*}}Earg2"}
13+
!FIRDialect-DAG: %[[SHAPE:.*]] = fir.shape %c10 : (index) -> !fir.shape<1>
14+
!FIRDialect-DAG: %[[ARG2_INIT_VAL:.*]] = fir.array_load %[[ARG2_PRIVATE:.*]](%[[SHAPE]]) : (!fir.ref<!fir.array<10xi32>>, !fir.shape<1>) -> !fir.array<10xi32>
15+
!FIRDialect-DAG: %[[FIRST_PRIVATE_UPDATES:.*]] = fir.do_loop
16+
!FIRDialect-DAG: {{.*}}fir.array_fetch{{.*}}
17+
!FIRDialect-DAG: {{.*}}fir.array_update{{.*}}
18+
!FIRDialect-DAG: fir.result{{.*}}
19+
!FIRDialect-DAG: }
20+
!FIRDialect-DAG: fir.array_merge_store %[[ARG2_INIT_VAL]], %[[FIRST_PRIVATE_UPDATES]] to %[[ARG2_PRIVATE]] : !fir.array<10xi32>, !fir.array<10xi32>, !fir.ref<!fir.array<10xi32>>
21+
!FIRDialect-DAG: %[[ARG3_BOX:.*]] = fir.load %[[ARG3]] : !fir.ref<!fir.box<!fir.heap<i32>>>
22+
!FIRDialect-DAG: %[[ARG3_ADDR:.*]] = fir.box_addr %[[ARG3_BOX]] : (!fir.box<!fir.heap<i32>>) -> !fir.heap<i32>
23+
!FIRDialect-DAG: %[[ARG3_PVT:.*]] = fir.alloca i32 {{{.*}}uniq_name = "{{.*}}Earg3"}
24+
!FIRDialect-DAG: %[[ARG3_PVT_LOAD:.*]] = fir.load %[[ARG3_ADDR]] : !fir.heap<i32>
25+
!FIRDialect-DAG: fir.store %[[ARG3_PVT_LOAD]] to %[[ARG3_PVT]] : !fir.ref<i32>
26+
!FIRDialect-DAG: omp.terminator
27+
!FIRDialect-DAG: }
1928

20-
!LLVMDialect: llvm.func @_QPfirstprivate_clause(%[[ARG1:.*]]: !llvm.ptr<i32>, %[[ARG2:.*]]: !llvm.ptr<array<10 x i32>>) {
21-
!LLVMIRDialect-DAG: %[[ALPHA:.*]] = llvm.alloca %{{.*}} x i32 {{{.*}}, uniq_name = "{{.*}}Ealpha"} : (i64) -> !llvm.ptr<i32>
22-
!LLVMIRDialect-DAG: %[[BETA:.*]] = llvm.alloca %{{.*}} x i32 {{{.*}}, uniq_name = "{{.*}}Ebeta"} : (i64) -> !llvm.ptr<i32>
23-
!LLVMIRDialect-DAG: %[[GAMA:.*]] = llvm.alloca %{{.*}} x i32 {{{.*}}, uniq_name = "{{.*}}Egama"} : (i64) -> !llvm.ptr<i32>
24-
!LLVMIRDialect-DAG: %[[ALPHA_ARRAY:.*]] = llvm.alloca %{{.*}} x !llvm.array<10 x i32> {{{.*}}, uniq_name = "{{.*}}Ealpha_array"} : (i64) -> !llvm.ptr<array<10 x i32>>
25-
!LLVMIRDialect: omp.parallel firstprivate(%[[ALPHA]] : !llvm.ptr<i32>, %[[BETA]] : !llvm.ptr<i32>, %[[GAMA]] : !llvm.ptr<i32>,
26-
!%[[ALPHA_ARRAY]] : !llvm.ptr<array<10 x i32>>, %[[ARG1]] : !llvm.ptr<i32>, %[[ARG2]] : !llvm.ptr<array<10 x i32>>) {
27-
!LLVMIRDialect: omp.terminator
28-
!LLVMIRDialect: }
29-
30-
subroutine firstprivate_clause(arg1, arg2)
29+
subroutine firstprivate_clause(arg1, arg2, arg3)
3130

3231
integer :: arg1, arg2(10)
33-
integer :: alpha, beta, gama
34-
integer :: alpha_array(10)
32+
integer, allocatable :: arg3
3533

36-
!$OMP PARALLEL FIRSTPRIVATE(alpha, beta, gama, alpha_array, arg1, arg2)
37-
print*, "FIRSTPRIVATE"
38-
print*, alpha, beta, gama
34+
!$OMP PARALLEL FIRSTPRIVATE(arg1, arg2, arg3)
35+
print*, arg1, arg2, arg3
3936
!$OMP END PARALLEL
4037

4138
end subroutine

0 commit comments

Comments
 (0)