Skip to content

Commit d59c7ff

Browse files
committed
[rebase][OpenMP] Apply D111051 - Add support for SIMD modifier
Some OpenMP local changes related to SIMD were done in #791 and touched llvm parts outside of flang. These parts were lost in the rebase/cannot be applied anymore since the files changed too much. The upstreaming of these changes is ongoing in: https://reviews.llvm.org/D111051 Try as much as possible to apply D111051 in a way that works with fir-dev environment.
1 parent 8073b6f commit d59c7ff

File tree

6 files changed

+87
-18
lines changed

6 files changed

+87
-18
lines changed

llvm/include/llvm/Frontend/OpenMP/OMPConstants.h

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,10 @@ enum class OMPScheduleType {
120120
Runtime = 37,
121121
Auto = 38, // auto
122122

123+
StaticBalancedChunked = 45, // static with chunk adjustment (e.g., simd)
124+
GuidedSimd = 46, // guided with chunk adjustment
125+
RuntimeSimd = 47, // runtime with chunk adjustment
126+
123127
ModifierMonotonic =
124128
(1 << 29), // Set if the monotonic schedule modifier was present
125129
ModifierNonmonotonic =

mlir/include/mlir/Dialect/OpenMP/OpenMPOps.td

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -139,11 +139,13 @@ def TerminatorOp : OpenMP_Op<"terminator", [Terminator]> {
139139
def OMP_SCHEDULE_MOD_None : StrEnumAttrCase<"none", 0>;
140140
def OMP_SCHEDULE_MOD_Monotonic : StrEnumAttrCase<"monotonic", 1>;
141141
def OMP_SCHEDULE_MOD_Nonmonotonic : StrEnumAttrCase<"nonmonotonic", 2>;
142+
def OMP_SCHEDULE_MOD_SIMD : StrEnumAttrCase<"simd", 3>;
142143

143144
def ScheduleModifier : StrEnumAttr<"ScheduleModifier", "OpenMP Schedule Modifier",
144145
[OMP_SCHEDULE_MOD_None,
145146
OMP_SCHEDULE_MOD_Monotonic,
146-
OMP_SCHEDULE_MOD_Nonmonotonic]>
147+
OMP_SCHEDULE_MOD_Nonmonotonic,
148+
OMP_SCHEDULE_MOD_SIMD]>
147149
{
148150
let cppNamespace = "::mlir::omp";
149151
}
@@ -226,7 +228,8 @@ def WsLoopOp : OpenMP_Op<"wsloop", [AttrSizedOperandSegments,
226228
OptionalAttr<SymbolRefArrayAttr>:$reductions,
227229
OptionalAttr<ScheduleKind>:$schedule_val,
228230
Optional<AnyType>:$schedule_chunk_var,
229-
OptionalAttr<ScheduleModifier>:$schedule_modifier,
231+
OptionalAttr<ScheduleModifier>:$schedule_modifiers,
232+
OptionalAttr<ScheduleModifier>:$simd_modifier,
230233
Confined<OptionalAttr<I64Attr>, [IntMinValue<0>]>:$collapse_val,
231234
UnitAttr:$nowait,
232235
Confined<OptionalAttr<I64Attr>, [IntMinValue<0>]>:$ordered_val,

mlir/lib/Dialect/OpenMP/IR/OpenMPDialect.cpp

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -278,7 +278,7 @@ parseScheduleClause(OpAsmParser &parser, SmallString<8> &schedule,
278278
}
279279

280280
// If there is a comma, we have one or more modifiers..
281-
if (succeeded(parser.parseOptionalComma())) {
281+
while (succeeded(parser.parseOptionalComma())) {
282282
StringRef mod;
283283
if (parser.parseKeyword(&mod))
284284
return failure();
@@ -294,14 +294,18 @@ parseScheduleClause(OpAsmParser &parser, SmallString<8> &schedule,
294294
/// Print schedule clause
295295
static void printScheduleClause(OpAsmPrinter &p, StringRef &sched,
296296
llvm::Optional<StringRef> modifier,
297+
llvm::Optional<StringRef> simd,
297298
Value scheduleChunkVar) {
298299
std::string schedLower = sched.lower();
299300
p << "(" << schedLower;
300301
if (scheduleChunkVar)
301302
p << " = " << scheduleChunkVar;
302303
if (modifier && modifier.getValue() != "none")
303304
p << ", " << modifier;
304-
p << ") ";
305+
if (simd && simd.getValue() != "none") {
306+
p << ", " << simd;
307+
}
308+
p << ")";
305309
}
306310

307311
//===----------------------------------------------------------------------===//
@@ -812,7 +816,11 @@ static ParseResult parseClauses(OpAsmParser &parser, OperationState &result,
812816
result.addAttribute("schedule_val", attr);
813817
if (modifiers.size() > 0) {
814818
auto mod = parser.getBuilder().getStringAttr(modifiers[0]);
815-
result.addAttribute("schedule_modifier", mod);
819+
result.addAttribute("schedule_modifiers", mod);
820+
if (modifiers.size() > 1) {
821+
mod = parser.getBuilder().getStringAttr(modifiers[1]);
822+
result.addAttribute("simd_modifier", mod);
823+
}
816824
}
817825
if (scheduleChunkSize) {
818826
auto chunkSizeType = parser.getBuilder().getI32Type();
@@ -933,8 +941,9 @@ static void printWsLoopOp(OpAsmPrinter &p, WsLoopOp op) {
933941

934942
if (auto sched = op.schedule_val()) {
935943
p << "schedule";
936-
printScheduleClause(p, sched.getValue(), op.schedule_modifier(),
937-
op.schedule_chunk_var());
944+
printScheduleClause(p, sched.getValue(), op.schedule_modifiers(),
945+
op.simd_modifier(), op.schedule_chunk_var());
946+
p << " ";
938947
}
939948

940949
if (auto collapse = op.collapse_val())

mlir/lib/Target/LLVMIR/Dialect/OpenMP/OpenMPToLLVMIRTranslation.cpp

Lines changed: 17 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -684,6 +684,13 @@ convertOmpWsLoop(Operation &opInst, llvm::IRBuilderBase &builder,
684684
ompBuilder->collapseLoops(diLoc, loopInfos, {});
685685

686686
allocaIP = findAllocaInsertPoint(builder, moduleTranslation);
687+
688+
bool isSimd = false;
689+
if (auto simd = loop.simd_modifier()) {
690+
omp::ScheduleModifier modifier = *omp::symbolizeScheduleModifier(*simd);
691+
isSimd = (modifier == omp::ScheduleModifier::simd);
692+
}
693+
687694
if (schedule == omp::ClauseScheduleKind::Static) {
688695
ompBuilder->applyStaticWorkshareLoop(ompLoc.DL, loopInfo, allocaIP,
689696
!loop.nowait(), chunk);
@@ -694,22 +701,28 @@ convertOmpWsLoop(Operation &opInst, llvm::IRBuilderBase &builder,
694701
schedType = llvm::omp::OMPScheduleType::DynamicChunked;
695702
break;
696703
case omp::ClauseScheduleKind::Guided:
697-
schedType = llvm::omp::OMPScheduleType::GuidedChunked;
704+
if (isSimd)
705+
schedType = llvm::omp::OMPScheduleType::GuidedSimd;
706+
else
707+
schedType = llvm::omp::OMPScheduleType::GuidedChunked;
698708
break;
699709
case omp::ClauseScheduleKind::Auto:
700710
schedType = llvm::omp::OMPScheduleType::Auto;
701711
break;
702712
case omp::ClauseScheduleKind::Runtime:
703-
schedType = llvm::omp::OMPScheduleType::Runtime;
713+
if (isSimd)
714+
schedType = llvm::omp::OMPScheduleType::RuntimeSimd;
715+
else
716+
schedType = llvm::omp::OMPScheduleType::Runtime;
704717
break;
705718
default:
706719
llvm_unreachable("Unknown schedule value");
707720
break;
708721
}
709722

710-
if (loop.schedule_modifier().hasValue()) {
723+
if (loop.schedule_modifiers().hasValue()) {
711724
omp::ScheduleModifier modifier =
712-
*omp::symbolizeScheduleModifier(loop.schedule_modifier().getValue());
725+
*omp::symbolizeScheduleModifier(loop.schedule_modifiers().getValue());
713726
switch (modifier) {
714727
case omp::ScheduleModifier::monotonic:
715728
schedType |= llvm::omp::OMPScheduleType::ModifierMonotonic;

mlir/test/Dialect/OpenMP/ops.mlir

Lines changed: 17 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -176,15 +176,29 @@ func @omp_wsloop_pretty(%lb : index, %ub : index, %step : index,
176176
omp.yield
177177
}
178178

179-
// CHECK: omp.wsloop (%{{.*}}) : index = (%{{.*}}) to (%{{.*}}) step (%{{.*}}) linear(%{{.*}} = %{{.*}} : memref<i32>) schedule(static)
179+
// CHECK: omp.wsloop (%{{.*}}) : index = (%{{.*}}) to (%{{.*}}) step (%{{.*}}) linear(%{{.*}} = %{{.*}} : memref<i32>) schedule(static, none)
180180
omp.wsloop (%iv) : index = (%lb) to (%ub) step (%step) schedule(static, none) lastprivate(%data_var : memref<i32>) linear(%data_var = %linear_var : memref<i32>) {
181181
omp.yield
182182
}
183183

184-
// CHECK: omp.wsloop (%{{.*}}) : index = (%{{.*}}) to (%{{.*}}) step (%{{.*}}) private(%{{.*}} : memref<i32>) firstprivate(%{{.*}} : memref<i32>) lastprivate(%{{.*}} : memref<i32>) linear(%{{.*}} = %{{.*}} : memref<i32>) schedule(static = %{{.*}}) collapse(3) ordered(2)
184+
// CHECK: omp.wsloop (%{{.*}}) : index = (%{{.*}}) to (%{{.*}}) step (%{{.*}}) private(%{{.*}} : memref<i32>) firstprivate(%{{.*}} : memref<i32>) lastprivate(%{{.*}} : memref<i32>) linear(%{{.*}} = %{{.*}} : memref<i32>) schedule(static = %{{.*}}, none) collapse(3) ordered(2)
185+
omp.wsloop (%iv) : index = (%lb) to (%ub) step (%step) ordered(2) private(%data_var : memref<i32>)
186+
firstprivate(%data_var : memref<i32>) lastprivate(%data_var : memref<i32>) linear(%data_var = %linear_var : memref<i32>)
187+
schedule(static = %chunk_var, none) collapse(3) {
188+
omp.yield
189+
}
190+
191+
// CHECK: omp.wsloop (%{{.*}}) : index = (%{{.*}}) to (%{{.*}}) step (%{{.*}}) private(%{{.*}} : memref<i32>) firstprivate(%{{.*}} : memref<i32>) lastprivate(%{{.*}} : memref<i32>) linear(%{{.*}} = %{{.*}} : memref<i32>) schedule(dynamic = %{{.*}}, nonmonotonic) collapse(3) ordered(2)
185192
omp.wsloop (%iv) : index = (%lb) to (%ub) step (%step) ordered(2) private(%data_var : memref<i32>)
186193
firstprivate(%data_var : memref<i32>) lastprivate(%data_var : memref<i32>) linear(%data_var = %linear_var : memref<i32>)
187-
schedule(static = %chunk_var) collapse(3) {
194+
schedule(dynamic = %chunk_var, nonmonotonic) collapse(3) {
195+
omp.yield
196+
}
197+
198+
// CHECK: omp.wsloop (%{{.*}}) : index = (%{{.*}}) to (%{{.*}}) step (%{{.*}}) private(%{{.*}} : memref<i32>) firstprivate(%{{.*}} : memref<i32>) lastprivate(%{{.*}} : memref<i32>) linear(%{{.*}} = %{{.*}} : memref<i32>) schedule(dynamic = %{{.*}}, monotonic) collapse(3) ordered(2)
199+
omp.wsloop (%iv) : index = (%lb) to (%ub) step (%step) ordered(2) private(%data_var : memref<i32>)
200+
firstprivate(%data_var : memref<i32>) lastprivate(%data_var : memref<i32>) linear(%data_var = %linear_var : memref<i32>)
201+
schedule(dynamic = %chunk_var, monotonic) collapse(3) {
188202
omp.yield
189203
}
190204

mlir/test/Target/LLVMIR/openmp-llvm.mlir

Lines changed: 30 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -420,7 +420,7 @@ llvm.func @wsloop_inclusive_2(%arg0: !llvm.ptr<f32>) {
420420
llvm.func @body(i64)
421421

422422
llvm.func @test_omp_wsloop_dynamic(%lb : i64, %ub : i64, %step : i64) -> () {
423-
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(dynamic) {
423+
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(dynamic, none) {
424424
// CHECK: call void @__kmpc_dispatch_init_8u
425425
// CHECK: %[[continue:.*]] = call i32 @__kmpc_dispatch_next_8u
426426
// CHECK: %[[cond:.*]] = icmp ne i32 %[[continue]], 0
@@ -432,7 +432,7 @@ llvm.func @test_omp_wsloop_dynamic(%lb : i64, %ub : i64, %step : i64) -> () {
432432
}
433433

434434
llvm.func @test_omp_wsloop_auto(%lb : i64, %ub : i64, %step : i64) -> () {
435-
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(auto) {
435+
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(auto, none) {
436436
// CHECK: call void @__kmpc_dispatch_init_8u
437437
// CHECK: %[[continue:.*]] = call i32 @__kmpc_dispatch_next_8u
438438
// CHECK: %[[cond:.*]] = icmp ne i32 %[[continue]], 0
@@ -444,7 +444,7 @@ llvm.func @test_omp_wsloop_auto(%lb : i64, %ub : i64, %step : i64) -> () {
444444
}
445445

446446
llvm.func @test_omp_wsloop_runtime(%lb : i64, %ub : i64, %step : i64) -> () {
447-
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(runtime) {
447+
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(runtime, none) {
448448
// CHECK: call void @__kmpc_dispatch_init_8u
449449
// CHECK: %[[continue:.*]] = call i32 @__kmpc_dispatch_next_8u
450450
// CHECK: %[[cond:.*]] = icmp ne i32 %[[continue]], 0
@@ -456,7 +456,7 @@ llvm.func @test_omp_wsloop_runtime(%lb : i64, %ub : i64, %step : i64) -> () {
456456
}
457457

458458
llvm.func @test_omp_wsloop_guided(%lb : i64, %ub : i64, %step : i64) -> () {
459-
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(guided) {
459+
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(guided, none) {
460460
// CHECK: call void @__kmpc_dispatch_init_8u
461461
// CHECK: %[[continue:.*]] = call i32 @__kmpc_dispatch_next_8u
462462
// CHECK: %[[cond:.*]] = icmp ne i32 %[[continue]], 0
@@ -521,6 +521,32 @@ llvm.func @omp_critical(%x : !llvm.ptr<i32>, %xval : i32) -> () {
521521

522522
// -----
523523

524+
llvm.func @test_omp_wsloop_dynamic_nonmonotonic(%lb : i64, %ub : i64, %step : i64) -> () {
525+
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(dynamic, nonmonotonic) {
526+
// CHECK: call void @__kmpc_dispatch_init_8u(%struct.ident_t* @{{.*}}, i32 %{{.*}}, i32 1073741859
527+
// CHECK: %[[continue:.*]] = call i32 @__kmpc_dispatch_next_8u
528+
// CHECK: %[[cond:.*]] = icmp ne i32 %[[continue]], 0
529+
// CHECK br i1 %[[cond]], label %omp_loop.header{{.*}}, label %omp_loop.exit{{.*}}
530+
llvm.call @body(%iv) : (i64) -> ()
531+
omp.yield
532+
}
533+
llvm.return
534+
}
535+
536+
llvm.func @test_omp_wsloop_dynamic_monotonic(%lb : i64, %ub : i64, %step : i64) -> () {
537+
omp.wsloop (%iv) : i64 = (%lb) to (%ub) step (%step) schedule(dynamic, monotonic) {
538+
// CHECK: call void @__kmpc_dispatch_init_8u(%struct.ident_t* @{{.*}}, i32 %{{.*}}, i32 536870947
539+
// CHECK: %[[continue:.*]] = call i32 @__kmpc_dispatch_next_8u
540+
// CHECK: %[[cond:.*]] = icmp ne i32 %[[continue]], 0
541+
// CHECK br i1 %[[cond]], label %omp_loop.header{{.*}}, label %omp_loop.exit{{.*}}
542+
llvm.call @body(%iv) : (i64) -> ()
543+
omp.yield
544+
}
545+
llvm.return
546+
}
547+
548+
// -----
549+
524550
// Check that the loop bounds are emitted in the correct location in case of
525551
// collapse. This only checks the overall shape of the IR, detailed checking
526552
// is done by the OpenMPIRBuilder.

0 commit comments

Comments
 (0)