@@ -96,8 +96,6 @@ class ArrayCopyAnalysis {
9696 return loadMapSets.lookup (load);
9797 }
9898
99- // / Get all the array value operations that use the original array value
100- // / as passed to `store`.
10199 void arrayMentions (llvm::SmallVectorImpl<mlir::Operation *> &mentions,
102100 ArrayLoadOp load);
103101
@@ -128,6 +126,27 @@ class ReachCollector {
128126 collectArrayMentionFrom (v);
129127 }
130128
129+ // Collect all the array_access ops in `block`. This recursively looks into
130+ // blocks in ops with regions.
131+ // FIXME: This is temporarily relying on the array_amend appearing in a
132+ // do_loop Region. This phase ordering assumption can be eliminated by using
133+ // dominance information to find the array_access ops or by scanning the
134+ // transitive closure of the amending array_access's users and the defs that
135+ // reach them.
136+ void collectAccesses (llvm::SmallVector<fir::ArrayAccessOp> &result,
137+ mlir::Block *block) {
138+ for (auto &op : *block) {
139+ if (auto access = mlir::dyn_cast<ArrayAccessOp>(op)) {
140+ LLVM_DEBUG (llvm::dbgs () << " adding access: " << access << ' \n ' );
141+ result.push_back (access);
142+ continue ;
143+ }
144+ for (auto ®ion : op.getRegions ())
145+ for (auto &bb : region.getBlocks ())
146+ collectAccesses (result, &bb);
147+ }
148+ }
149+
131150 void collectArrayMentionFrom (mlir::Operation *op, mlir::Value val) {
132151 // `val` is defined by an Op, process the defining Op.
133152 // If `val` is defined by a region containing Op, we want to drill down
@@ -175,9 +194,18 @@ class ReachCollector {
175194 return ;
176195 }
177196
197+ // Scan the uses of amend's memref
198+ if (auto amend = mlir::dyn_cast<ArrayAmendOp>(op)) {
199+ reach.push_back (op);
200+ llvm::SmallVector<ArrayAccessOp> accesses;
201+ collectAccesses (accesses, op->getBlock ());
202+ for (auto access : accesses)
203+ collectArrayMentionFrom (access.getResult ());
204+ }
205+
178206 // Otherwise, Op does not contain a region so just chase its operands.
179- if (mlir::isa<ArrayAccessOp, ArrayAmendOp, ArrayLoadOp, ArrayUpdateOp,
180- ArrayModifyOp, ArrayFetchOp>(op)) {
207+ if (mlir::isa<ArrayAccessOp, ArrayLoadOp, ArrayUpdateOp, ArrayModifyOp ,
208+ ArrayFetchOp>(op)) {
181209 LLVM_DEBUG (llvm::dbgs () << " add " << *op << " to reachable set\n " );
182210 reach.push_back (op);
183211 }
@@ -418,29 +446,41 @@ static bool conflictOnMerge(llvm::ArrayRef<mlir::Operation *> mentions) {
418446 llvm::SmallVector<mlir::Value> indices;
419447 LLVM_DEBUG (llvm::dbgs () << " check merge conflict on with " << mentions.size ()
420448 << " mentions on the list\n " );
449+ bool valSeen = false ;
450+ bool refSeen = false ;
421451 for (auto *op : mentions) {
422452 llvm::SmallVector<mlir::Value> compareVector;
423453 if (auto u = mlir::dyn_cast<ArrayUpdateOp>(op)) {
454+ valSeen = true ;
424455 if (indices.empty ()) {
425456 indices = u.indices ();
426457 continue ;
427458 }
428459 compareVector = u.indices ();
429460 } else if (auto f = mlir::dyn_cast<ArrayModifyOp>(op)) {
461+ valSeen = true ;
430462 if (indices.empty ()) {
431463 indices = f.indices ();
432464 continue ;
433465 }
434466 compareVector = f.indices ();
435467 } else if (auto f = mlir::dyn_cast<ArrayFetchOp>(op)) {
468+ valSeen = true ;
436469 if (indices.empty ()) {
437470 indices = f.indices ();
438471 continue ;
439472 }
440473 compareVector = f.indices ();
441- } else if (mlir::isa<ArrayAccessOp, ArrayAmendOp>(op)) {
442- // Mixed by-value and by-reference? Be conservative.
443- return true ;
474+ } else if (auto f = mlir::dyn_cast<ArrayAccessOp>(op)) {
475+ refSeen = true ;
476+ if (indices.empty ()) {
477+ indices = f.indices ();
478+ continue ;
479+ }
480+ compareVector = f.indices ();
481+ } else if (mlir::isa<ArrayAmendOp>(op)) {
482+ refSeen = true ;
483+ continue ;
444484 } else {
445485 mlir::emitError (op->getLoc (), " unexpected operation in analysis" );
446486 }
@@ -451,7 +491,7 @@ static bool conflictOnMerge(llvm::ArrayRef<mlir::Operation *> mentions) {
451491 return true ;
452492 LLVM_DEBUG (llvm::dbgs () << " vectors compare equal\n " );
453493 }
454- return false ;
494+ return valSeen && refSeen ;
455495}
456496
457497// / With element-by-reference semantics, an amended array with more than once
@@ -493,7 +533,7 @@ amendingAccess(llvm::ArrayRef<mlir::Operation *> mentions) {
493533}
494534
495535// Are any conflicts present? The conflicts detected here are described above.
496- inline bool conflictDetected (llvm::ArrayRef<mlir::Operation *> reach,
536+ static bool conflictDetected (llvm::ArrayRef<mlir::Operation *> reach,
497537 llvm::ArrayRef<mlir::Operation *> mentions,
498538 ArrayMergeStoreOp st) {
499539 return conflictOnLoad (reach, st) || conflictOnMerge (mentions);
@@ -522,8 +562,8 @@ void ArrayCopyAnalysis::construct(mlir::MutableArrayRef<mlir::Region> regions) {
522562 << st.original () << ' \n ' );
523563 conflicts.insert (&op);
524564 conflicts.insert (st.original ().getDefiningOp ());
525- if (refConflict )
526- amendAccesses.insert (amendingAccess (mentions) );
565+ if (auto *access = amendingAccess (mentions) )
566+ amendAccesses.insert (access );
527567 }
528568 auto *ld = st.original ().getDefiningOp ();
529569 LLVM_DEBUG (llvm::dbgs ()
0 commit comments