Skip to content

Commit 8379767

Browse files
Meinersburkiranchandramohan
authored andcommitted
[OMPIRBuilder] Clarify CanonicalLoopInfo. NFC.
Add in-source documentation on how CanonicalLoopInfo is intended to be used. In particular, clarify what parts of a CanonicalLoopInfo is considered part of the loop, that those parts must be side-effect free, and that InsertPoints to instructions outside those parts can be expected to be preserved after method calls implementing loop-associated directives. CanonicalLoopInfo are now invalidated after it does not describe canonical loop anymore and asserts when trying to use it afterwards. In addition, rename `createXYZWorkshareLoop` to `applyXYZWorkshareLoop` and remove the update location to avoid that the impression that they insert something from scratch at that location where in reality its InsertPoint is ignored. createStaticWorkshareLoop does not return a CanonicalLoopInfo anymore. First, it was not a canonical loop in the clarified sense (containing side-effects in form of calls to the OpenMP runtime). Second, it is ambiguous which of the two possible canonical loops it should actually return. It will not be needed before a feature expected to be introduced in OpenMP 6.0 Also see discussion in D105706. Reviewed By: ftynse Differential Revision: https://reviews.llvm.org/D107540
1 parent 3fac959 commit 8379767

File tree

5 files changed

+259
-106
lines changed

5 files changed

+259
-106
lines changed

clang/lib/CodeGen/CGStmtOpenMP.cpp

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3594,7 +3594,8 @@ void CodeGenFunction::EmitOMPForDirective(const OMPForDirective &S) {
35943594
CGM.getOpenMPRuntime().getOMPBuilder();
35953595
llvm::OpenMPIRBuilder::InsertPointTy AllocaIP(
35963596
AllocaInsertPt->getParent(), AllocaInsertPt->getIterator());
3597-
OMPBuilder.createWorkshareLoop(Builder, CLI, AllocaIP, NeedsBarrier);
3597+
OMPBuilder.applyWorkshareLoop(Builder.getCurrentDebugLocation(), CLI,
3598+
AllocaIP, NeedsBarrier);
35983599
return;
35993600
}
36003601

llvm/include/llvm/Frontend/OpenMP/OMPIRBuilder.h

Lines changed: 173 additions & 57 deletions
Original file line numberDiff line numberDiff line change
@@ -257,18 +257,17 @@ class OpenMPIRBuilder {
257257
///
258258
/// * Sign of the step and the comparison operator might disagree:
259259
///
260-
/// for (int i = 0; i < 42; --i)
260+
/// for (int i = 0; i < 42; i -= 1u)
261261
///
262262
//
263263
/// \param Loc The insert and source location description.
264264
/// \param BodyGenCB Callback that will generate the loop body code.
265265
/// \param Start Value of the loop counter for the first iterations.
266-
/// \param Stop Loop counter values past this will stop the the
267-
/// iterations.
266+
/// \param Stop Loop counter values past this will stop the loop.
268267
/// \param Step Loop counter increment after each iteration; negative
269-
/// means counting down. \param IsSigned Whether Start, Stop
270-
/// and Stop are signed integers.
271-
/// \param InclusiveStop Whether \p Stop itself is a valid value for the loop
268+
/// means counting down.
269+
/// \param IsSigned Whether Start, Stop and Step are signed integers.
270+
/// \param InclusiveStop Whether \p Stop itself is a valid value for the loop
272271
/// counter.
273272
/// \param ComputeIP Insertion point for instructions computing the trip
274273
/// count. Can be used to ensure the trip count is available
@@ -335,7 +334,7 @@ class OpenMPIRBuilder {
335334
/// has a trip count of 0). This is permitted by the OpenMP specification.
336335
///
337336
/// \param DL Debug location for instructions added for collapsing,
338-
/// such as instructions to compute derive the input loop's
337+
/// such as instructions to compute/derive the input loop's
339338
/// induction variables.
340339
/// \param Loops Loops in the loop nest to collapse. Loops are specified
341340
/// from outermost-to-innermost and every control flow of a
@@ -358,8 +357,16 @@ class OpenMPIRBuilder {
358357
/// the current thread, updates the relevant instructions in the canonical
359358
/// loop and calls to an OpenMP runtime finalization function after the loop.
360359
///
361-
/// \param Loc The source location description, the insertion location
362-
/// is not used.
360+
/// TODO: Workshare loops with static scheduling may contain up to two loops
361+
/// that fulfill the requirements of an OpenMP canonical loop. One for
362+
/// iterating over all iterations of a chunk and another one for iterating
363+
/// over all chunks that are executed on the same thread. Returning
364+
/// CanonicalLoopInfo objects representing them may eventually be useful for
365+
/// the apply clause planned in OpenMP 6.0, but currently whether these are
366+
/// canonical loops is irrelevant.
367+
///
368+
/// \param DL Debug location for instructions added for the
369+
/// workshare-loop construct itself.
363370
/// \param CLI A descriptor of the canonical loop to workshare.
364371
/// \param AllocaIP An insertion point for Alloca instructions usable in the
365372
/// preheader of the loop.
@@ -368,12 +375,11 @@ class OpenMPIRBuilder {
368375
/// \param Chunk The size of loop chunk considered as a unit when
369376
/// scheduling. If \p nullptr, defaults to 1.
370377
///
371-
/// \returns Updated CanonicalLoopInfo.
372-
CanonicalLoopInfo *createStaticWorkshareLoop(const LocationDescription &Loc,
373-
CanonicalLoopInfo *CLI,
374-
InsertPointTy AllocaIP,
375-
bool NeedsBarrier,
376-
Value *Chunk = nullptr);
378+
/// \returns Point where to insert code after the workshare construct.
379+
InsertPointTy applyStaticWorkshareLoop(DebugLoc DL, CanonicalLoopInfo *CLI,
380+
InsertPointTy AllocaIP,
381+
bool NeedsBarrier,
382+
Value *Chunk = nullptr);
377383

378384
/// Modifies the canonical loop to be a dynamically-scheduled workshare loop.
379385
///
@@ -382,8 +388,9 @@ class OpenMPIRBuilder {
382388
/// turn it into a workshare loop. In particular, it calls to an OpenMP
383389
/// runtime function in the preheader to obtain, and then in each iteration
384390
/// to update the loop counter.
385-
/// \param Loc The source location description, the insertion location
386-
/// is not used.
391+
///
392+
/// \param DL Debug location for instructions added for the
393+
/// workshare-loop construct itself.
387394
/// \param CLI A descriptor of the canonical loop to workshare.
388395
/// \param AllocaIP An insertion point for Alloca instructions usable in the
389396
/// preheader of the loop.
@@ -393,13 +400,12 @@ class OpenMPIRBuilder {
393400
/// \param Chunk The size of loop chunk considered as a unit when
394401
/// scheduling. If \p nullptr, defaults to 1.
395402
///
396-
/// \returns Point where to insert code after the loop.
397-
InsertPointTy createDynamicWorkshareLoop(const LocationDescription &Loc,
398-
CanonicalLoopInfo *CLI,
399-
InsertPointTy AllocaIP,
400-
omp::OMPScheduleType SchedType,
401-
bool NeedsBarrier,
402-
Value *Chunk = nullptr);
403+
/// \returns Point where to insert code after the workshare construct.
404+
InsertPointTy applyDynamicWorkshareLoop(DebugLoc DL, CanonicalLoopInfo *CLI,
405+
InsertPointTy AllocaIP,
406+
omp::OMPScheduleType SchedType,
407+
bool NeedsBarrier,
408+
Value *Chunk = nullptr);
403409

404410
/// Modifies the canonical loop to be a workshare loop.
405411
///
@@ -410,19 +416,17 @@ class OpenMPIRBuilder {
410416
/// the current thread, updates the relevant instructions in the canonical
411417
/// loop and calls to an OpenMP runtime finalization function after the loop.
412418
///
413-
/// \param Loc The source location description, the insertion location
414-
/// is not used.
419+
/// \param DL Debug location for instructions added for the
420+
/// workshare-loop construct itself.
415421
/// \param CLI A descriptor of the canonical loop to workshare.
416422
/// \param AllocaIP An insertion point for Alloca instructions usable in the
417423
/// preheader of the loop.
418424
/// \param NeedsBarrier Indicates whether a barrier must be insterted after
419425
/// the loop.
420426
///
421-
/// \returns Updated CanonicalLoopInfo.
422-
CanonicalLoopInfo *createWorkshareLoop(const LocationDescription &Loc,
423-
CanonicalLoopInfo *CLI,
424-
InsertPointTy AllocaIP,
425-
bool NeedsBarrier);
427+
/// \returns Point where to insert code after the workshare construct.
428+
InsertPointTy applyWorkshareLoop(DebugLoc DL, CanonicalLoopInfo *CLI,
429+
InsertPointTy AllocaIP, bool NeedsBarrier);
426430

427431
/// Tile a loop nest.
428432
///
@@ -637,6 +641,10 @@ class OpenMPIRBuilder {
637641
Constant *getOrCreateSrcLocStr(StringRef FunctionName, StringRef FileName,
638642
unsigned Line, unsigned Column);
639643

644+
/// Return the (LLVM-IR) string describing the DebugLoc \p DL. Use \p F as
645+
/// fallback if \p DL does not specify the function name.
646+
Constant *getOrCreateSrcLocStr(DebugLoc DL, Function *F = nullptr);
647+
640648
/// Return the (LLVM-IR) string describing the source location \p Loc.
641649
Constant *getOrCreateSrcLocStr(const LocationDescription &Loc);
642650

@@ -1193,7 +1201,25 @@ class OpenMPIRBuilder {
11931201
/// The control-flow structure is standardized for easy consumption by
11941202
/// directives associated with loops. For instance, the worksharing-loop
11951203
/// construct may change this control flow such that each loop iteration is
1196-
/// executed on only one thread.
1204+
/// executed on only one thread. The constraints of a canonical loop in brief
1205+
/// are:
1206+
///
1207+
/// * The number of loop iterations must have been computed before entering the
1208+
/// loop.
1209+
///
1210+
/// * Has an (unsigned) logical induction variable that starts at zero and
1211+
/// increments by one.
1212+
///
1213+
/// * The loop's CFG itself has no side-effects. The OpenMP specification
1214+
/// itself allows side-effects, but the order in which they happen, including
1215+
/// how often or whether at all, is unspecified. We expect that the frontend
1216+
/// will emit those side-effect instructions somewhere (e.g. before the loop)
1217+
/// such that the CanonicalLoopInfo itself can be side-effect free.
1218+
///
1219+
/// Keep in mind that CanonicalLoopInfo is meant to only describe a repeated
1220+
/// execution of a loop body that satifies these constraints. It does NOT
1221+
/// represent arbitrary SESE regions that happen to contain a loop. Do not use
1222+
/// CanonicalLoopInfo for such purposes.
11971223
///
11981224
/// The control flow can be described as follows:
11991225
///
@@ -1213,73 +1239,149 @@ class OpenMPIRBuilder {
12131239
/// |
12141240
/// After
12151241
///
1216-
/// Code in the header, condition block, latch and exit block must not have any
1217-
/// side-effect. The body block is the single entry point into the loop body,
1218-
/// which may contain arbitrary control flow as long as all control paths
1219-
/// eventually branch to the latch block.
1242+
/// The loop is thought to start at PreheaderIP (at the Preheader's terminator,
1243+
/// including) and end at AfterIP (at the After's first instruction, excluding).
1244+
/// That is, instructions in the Preheader and After blocks (except the
1245+
/// Preheader's terminator) are out of CanonicalLoopInfo's control and may have
1246+
/// side-effects. Typically, the Preheader is used to compute the loop's trip
1247+
/// count. The instructions from BodyIP (at the Body block's first instruction,
1248+
/// excluding) until the Latch are also considered outside CanonicalLoopInfo's
1249+
/// control and thus can have side-effects. The body block is the single entry
1250+
/// point into the loop body, which may contain arbitrary control flow as long
1251+
/// as all control paths eventually branch to the Latch block.
1252+
///
1253+
/// TODO: Consider adding another standardized BasicBlock between Body CFG and
1254+
/// Latch to guarantee that there is only a single edge to the latch. It would
1255+
/// make loop transformations easier to not needing to consider multiple
1256+
/// predecessors of the latch (See redirectAllPredecessorsTo) and would give us
1257+
/// an equivalant to PreheaderIP, AfterIP and BodyIP for inserting code that
1258+
/// executes after each body iteration.
1259+
///
1260+
/// There must be no loop-carried dependencies through llvm::Values. This is
1261+
/// equivalant to that the Latch has no PHINode and the Header's only PHINode is
1262+
/// for the induction variable.
1263+
///
1264+
/// All code in Header, Cond, Latch and Exit (plus the terminator of the
1265+
/// Preheader) are CanonicalLoopInfo's responsibility and their build-up checked
1266+
/// by assertOK(). They are expected to not be modified unless explicitly
1267+
/// modifying the CanonicalLoopInfo through a methods that applies a OpenMP
1268+
/// loop-associated construct such as applyWorkshareLoop, tileLoops, unrollLoop,
1269+
/// etc. These methods usually invalidate the CanonicalLoopInfo and re-use its
1270+
/// basic blocks. After invalidation, the CanonicalLoopInfo must not be used
1271+
/// anymore as its underlying control flow may not exist anymore.
1272+
/// Loop-transformation methods such as tileLoops, collapseLoops and unrollLoop
1273+
/// may also return a new CanonicalLoopInfo that can be passed to other
1274+
/// loop-associated construct implementing methods. These loop-transforming
1275+
/// methods may either create a new CanonicalLoopInfo usually using
1276+
/// createLoopSkeleton and invalidate the input CanonicalLoopInfo, or reuse and
1277+
/// modify one of the input CanonicalLoopInfo and return it as representing the
1278+
/// modified loop. What is done is an implementation detail of
1279+
/// transformation-implementing method and callers should always assume that the
1280+
/// CanonicalLoopInfo passed to it is invalidated and a new object is returned.
1281+
/// Returned CanonicalLoopInfo have the same structure and guarantees as the one
1282+
/// created by createCanonicalLoop, such that transforming methods do not have
1283+
/// to special case where the CanonicalLoopInfo originated from.
1284+
///
1285+
/// Generally, methods consuming CanonicalLoopInfo do not need an
1286+
/// OpenMPIRBuilder::InsertPointTy as argument, but use the locations of the
1287+
/// CanonicalLoopInfo to insert new or modify existing instructions. Unless
1288+
/// documented otherwise, methods consuming CanonicalLoopInfo do not invalidate
1289+
/// any InsertPoint that is outside CanonicalLoopInfo's control. Specifically,
1290+
/// any InsertPoint in the Preheader, After or Block can still be used after
1291+
/// calling such a method.
1292+
///
1293+
/// TODO: Provide mechanisms for exception handling and cancellation points.
12201294
///
1221-
/// Defined outside OpenMPIRBuilder because one cannot forward-declare nested
1222-
/// classes.
1295+
/// Defined outside OpenMPIRBuilder because nested classes cannot be
1296+
/// forward-declared, e.g. to avoid having to include the entire OMPIRBuilder.h.
12231297
class CanonicalLoopInfo {
12241298
friend class OpenMPIRBuilder;
12251299

12261300
private:
1227-
/// Whether this object currently represents a loop.
1228-
bool IsValid = false;
1229-
1230-
BasicBlock *Preheader;
1231-
BasicBlock *Header;
1232-
BasicBlock *Cond;
1233-
BasicBlock *Body;
1234-
BasicBlock *Latch;
1235-
BasicBlock *Exit;
1236-
BasicBlock *After;
1301+
BasicBlock *Preheader = nullptr;
1302+
BasicBlock *Header = nullptr;
1303+
BasicBlock *Cond = nullptr;
1304+
BasicBlock *Body = nullptr;
1305+
BasicBlock *Latch = nullptr;
1306+
BasicBlock *Exit = nullptr;
1307+
BasicBlock *After = nullptr;
12371308

12381309
/// Add the control blocks of this loop to \p BBs.
12391310
///
12401311
/// This does not include any block from the body, including the one returned
12411312
/// by getBody().
1313+
///
1314+
/// FIXME: This currently includes the Preheader and After blocks even though
1315+
/// their content is (mostly) not under CanonicalLoopInfo's control.
1316+
/// Re-evaluated whether this makes sense.
12421317
void collectControlBlocks(SmallVectorImpl<BasicBlock *> &BBs);
12431318

12441319
public:
1320+
/// Returns whether this object currently represents the IR of a loop. If
1321+
/// returning false, it may have been consumed by a loop transformation or not
1322+
/// been intialized. Do not use in this case;
1323+
bool isValid() const { return Header; }
1324+
12451325
/// The preheader ensures that there is only a single edge entering the loop.
12461326
/// Code that must be execute before any loop iteration can be emitted here,
12471327
/// such as computing the loop trip count and begin lifetime markers. Code in
12481328
/// the preheader is not considered part of the canonical loop.
1249-
BasicBlock *getPreheader() const { return Preheader; }
1329+
BasicBlock *getPreheader() const {
1330+
assert(isValid() && "Requires a valid canonical loop");
1331+
return Preheader;
1332+
}
12501333

12511334
/// The header is the entry for each iteration. In the canonical control flow,
12521335
/// it only contains the PHINode for the induction variable.
1253-
BasicBlock *getHeader() const { return Header; }
1336+
BasicBlock *getHeader() const {
1337+
assert(isValid() && "Requires a valid canonical loop");
1338+
return Header;
1339+
}
12541340

12551341
/// The condition block computes whether there is another loop iteration. If
12561342
/// yes, branches to the body; otherwise to the exit block.
1257-
BasicBlock *getCond() const { return Cond; }
1343+
BasicBlock *getCond() const {
1344+
assert(isValid() && "Requires a valid canonical loop");
1345+
return Cond;
1346+
}
12581347

12591348
/// The body block is the single entry for a loop iteration and not controlled
12601349
/// by CanonicalLoopInfo. It can contain arbitrary control flow but must
12611350
/// eventually branch to the \p Latch block.
1262-
BasicBlock *getBody() const { return Body; }
1351+
BasicBlock *getBody() const {
1352+
assert(isValid() && "Requires a valid canonical loop");
1353+
return Body;
1354+
}
12631355

12641356
/// Reaching the latch indicates the end of the loop body code. In the
12651357
/// canonical control flow, it only contains the increment of the induction
12661358
/// variable.
1267-
BasicBlock *getLatch() const { return Latch; }
1359+
BasicBlock *getLatch() const {
1360+
assert(isValid() && "Requires a valid canonical loop");
1361+
return Latch;
1362+
}
12681363

12691364
/// Reaching the exit indicates no more iterations are being executed.
1270-
BasicBlock *getExit() const { return Exit; }
1365+
BasicBlock *getExit() const {
1366+
assert(isValid() && "Requires a valid canonical loop");
1367+
return Exit;
1368+
}
12711369

12721370
/// The after block is intended for clean-up code such as lifetime end
12731371
/// markers. It is separate from the exit block to ensure, analogous to the
12741372
/// preheader, it having just a single entry edge and being free from PHI
12751373
/// nodes should there be multiple loop exits (such as from break
12761374
/// statements/cancellations).
1277-
BasicBlock *getAfter() const { return After; }
1375+
BasicBlock *getAfter() const {
1376+
assert(isValid() && "Requires a valid canonical loop");
1377+
return After;
1378+
}
12781379

12791380
/// Returns the llvm::Value containing the number of loop iterations. It must
12801381
/// be valid in the preheader and always interpreted as an unsigned integer of
12811382
/// any bit-width.
12821383
Value *getTripCount() const {
1384+
assert(isValid() && "Requires a valid canonical loop");
12831385
Instruction *CmpI = &Cond->front();
12841386
assert(isa<CmpInst>(CmpI) && "First inst must compare IV with TripCount");
12851387
return CmpI->getOperand(1);
@@ -1288,33 +1390,47 @@ class CanonicalLoopInfo {
12881390
/// Returns the instruction representing the current logical induction
12891391
/// variable. Always unsigned, always starting at 0 with an increment of one.
12901392
Instruction *getIndVar() const {
1393+
assert(isValid() && "Requires a valid canonical loop");
12911394
Instruction *IndVarPHI = &Header->front();
12921395
assert(isa<PHINode>(IndVarPHI) && "First inst must be the IV PHI");
12931396
return IndVarPHI;
12941397
}
12951398

12961399
/// Return the type of the induction variable (and the trip count).
1297-
Type *getIndVarType() const { return getIndVar()->getType(); }
1400+
Type *getIndVarType() const {
1401+
assert(isValid() && "Requires a valid canonical loop");
1402+
return getIndVar()->getType();
1403+
}
12981404

12991405
/// Return the insertion point for user code before the loop.
13001406
OpenMPIRBuilder::InsertPointTy getPreheaderIP() const {
1407+
assert(isValid() && "Requires a valid canonical loop");
13011408
return {Preheader, std::prev(Preheader->end())};
13021409
};
13031410

13041411
/// Return the insertion point for user code in the body.
13051412
OpenMPIRBuilder::InsertPointTy getBodyIP() const {
1413+
assert(isValid() && "Requires a valid canonical loop");
13061414
return {Body, Body->begin()};
13071415
};
13081416

13091417
/// Return the insertion point for user code after the loop.
13101418
OpenMPIRBuilder::InsertPointTy getAfterIP() const {
1419+
assert(isValid() && "Requires a valid canonical loop");
13111420
return {After, After->begin()};
13121421
};
13131422

1314-
Function *getFunction() const { return Header->getParent(); }
1423+
Function *getFunction() const {
1424+
assert(isValid() && "Requires a valid canonical loop");
1425+
return Header->getParent();
1426+
}
13151427

13161428
/// Consistency self-check.
13171429
void assertOK() const;
1430+
1431+
/// Invalidate this loop. That is, the underlying IR does not fulfill the
1432+
/// requirements of an OpenMP canonical loop anymore.
1433+
void invalidate();
13181434
};
13191435

13201436
} // end namespace llvm

0 commit comments

Comments
 (0)