Skip to content

Commit 1946a1c

Browse files
authored
Merge pull request #1183 from schweitzpgi/ch-bug8
Fix assertion failure. Do not add to an iteration space when expression
2 parents 2104989 + 8ff911a commit 1946a1c

File tree

3 files changed

+58
-1
lines changed

3 files changed

+58
-1
lines changed

flang/lib/Lower/ConvertExpr.cpp

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5463,6 +5463,9 @@ class ArrayExprLowering {
54635463

54645464
/// Lower the path (`revPath`, in reverse) to be appended to an array_fetch
54655465
/// or array_update op. This function is evaluated from a continuation.
5466+
///
5467+
/// TODO: This needs to deal with array's with initial bounds other than 1.
5468+
/// TODO: Thread type parameters correctly.
54665469
std::tuple<llvm::SmallVector<mlir::Value>, mlir::Type,
54675470
llvm::SmallVector<mlir::Value>>
54685471
lowerPath(mlir::Location loc, llvm::ArrayRef<PathComponent> revPath,
@@ -5493,6 +5496,9 @@ class ArrayExprLowering {
54935496
return genAccessByVector(loc, genArrFetch, iters, dim++);
54945497
},
54955498
[&](const Fortran::evaluate::Triplet &t) -> mlir::Value {
5499+
if (iters.empty()) {
5500+
TODO(loc, "triplet in array; should this be boxed?");
5501+
}
54965502
auto impliedIter = iters.iterValue(dim++);
54975503
// FIXME: initial should be the lbound of this array. Use 1. See
54985504
// getLBound().
@@ -5520,7 +5526,6 @@ class ArrayExprLowering {
55205526
auto vi = builder.createConvert(loc, idxTy, v);
55215527
result.push_back(builder.create<mlir::arith::AddIOp>(loc, vi, one));
55225528
}
5523-
dim += iters.iterVec().size();
55245529
};
55255530
for (const auto &v : llvm::reverse(revPath)) {
55265531
std::visit(

flang/lib/Lower/IterationSpace.h

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -265,6 +265,7 @@ class ImplicitIterSpace
265265
return stack;
266266
}
267267

268+
// Cleanup at the end of a WHERE statement or construct.
268269
void shrinkStack() {
269270
Base::shrinkStack();
270271
if (stack.empty())

flang/test/Lower/forall-2.f90

Lines changed: 51 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -126,3 +126,54 @@ subroutine slice_with_explicit_iters
126126
! CHECK: return
127127
! CHECK: }
128128
end subroutine slice_with_explicit_iters
129+
130+
! CHECK-LABEL: func @_QPembox_argument_with_slice(
131+
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<1xi32>>, %[[VAL_1:.*]]: !fir.ref<!fir.array<2x2xi32>>) {
132+
! CHECK: %[[VAL_2:.*]] = fir.alloca i32 {adapt.valuebyref, bindc_name = "i"}
133+
! CHECK: %[[VAL_3:.*]] = arith.constant 1 : index
134+
! CHECK: %[[VAL_4:.*]] = arith.constant 2 : index
135+
! CHECK: %[[VAL_5:.*]] = arith.constant 2 : index
136+
! CHECK: %[[VAL_6:.*]] = arith.constant 1 : i32
137+
! CHECK: %[[VAL_7:.*]] = fir.convert %[[VAL_6]] : (i32) -> index
138+
! CHECK: %[[VAL_8:.*]] = arith.constant 1 : i32
139+
! CHECK: %[[VAL_9:.*]] = fir.convert %[[VAL_8]] : (i32) -> index
140+
! CHECK: %[[VAL_10:.*]] = arith.constant 1 : index
141+
! CHECK: %[[VAL_11:.*]] = fir.shape %[[VAL_3]] : (index) -> !fir.shape<1>
142+
! CHECK: %[[VAL_12:.*]] = fir.array_load %[[VAL_0]](%[[VAL_11]]) : (!fir.ref<!fir.array<1xi32>>, !fir.shape<1>) -> !fir.array<1xi32>
143+
! CHECK: %[[VAL_13:.*]] = fir.do_loop %[[VAL_14:.*]] = %[[VAL_7]] to %[[VAL_9]] step %[[VAL_10]] unordered iter_args(%[[VAL_15:.*]] = %[[VAL_12]]) -> (!fir.array<1xi32>) {
144+
! CHECK: %[[VAL_16:.*]] = fir.convert %[[VAL_14]] : (index) -> i32
145+
! CHECK: fir.store %[[VAL_16]] to %[[VAL_2]] : !fir.ref<i32>
146+
! CHECK: %[[VAL_17:.*]] = arith.constant 1 : i32
147+
! CHECK: %[[VAL_18:.*]] = arith.constant 1 : index
148+
! CHECK: %[[VAL_19:.*]] = arith.addi %[[VAL_18]], %[[VAL_4]] : index
149+
! CHECK: %[[VAL_20:.*]] = arith.subi %[[VAL_19]], %[[VAL_18]] : index
150+
! CHECK: %[[VAL_21:.*]] = arith.constant 1 : i64
151+
! CHECK: %[[VAL_22:.*]] = fir.load %[[VAL_2]] : !fir.ref<i32>
152+
! CHECK: %[[VAL_23:.*]] = fir.convert %[[VAL_22]] : (i32) -> i64
153+
! CHECK: %[[VAL_24:.*]] = fir.undefined index
154+
! CHECK: %[[VAL_25:.*]] = fir.shape %[[VAL_4]], %[[VAL_5]] : (index, index) -> !fir.shape<2>
155+
! CHECK: %[[VAL_26:.*]] = fir.slice %[[VAL_18]], %[[VAL_20]], %[[VAL_21]], %[[VAL_23]], %[[VAL_24]], %[[VAL_24]] : (index, index, i64, i64, index, index) -> !fir.slice<2>
156+
! CHECK: %[[VAL_27:.*]] = fir.embox %[[VAL_1]](%[[VAL_25]]) {{\[}}%[[VAL_26]]] : (!fir.ref<!fir.array<2x2xi32>>, !fir.shape<2>, !fir.slice<2>) -> !fir.box<!fir.array<?xi32>>
157+
! CHECK: %[[VAL_28:.*]] = fir.call @_QPe(%[[VAL_27]]) : (!fir.box<!fir.array<?xi32>>) -> i32
158+
! CHECK: %[[VAL_29:.*]] = arith.addi %[[VAL_28]], %[[VAL_17]] : i32
159+
! CHECK: %[[VAL_30:.*]] = fir.load %[[VAL_2]] : !fir.ref<i32>
160+
! CHECK: %[[VAL_31:.*]] = fir.convert %[[VAL_30]] : (i32) -> i64
161+
! CHECK: %[[VAL_32:.*]] = fir.convert %[[VAL_31]] : (i64) -> index
162+
! CHECK: %[[VAL_33:.*]] = fir.array_update %[[VAL_15]], %[[VAL_29]], %[[VAL_32]] {Fortran.offsets} : (!fir.array<1xi32>, i32, index) -> !fir.array<1xi32>
163+
! CHECK: fir.result %[[VAL_33]] : !fir.array<1xi32>
164+
! CHECK: }
165+
! CHECK: fir.array_merge_store %[[VAL_12]], %[[VAL_34:.*]] to %[[VAL_0]] : !fir.array<1xi32>, !fir.array<1xi32>, !fir.ref<!fir.array<1xi32>>
166+
subroutine embox_argument_with_slice(a,b)
167+
interface
168+
pure integer function e(a)
169+
integer, intent(in) :: a(:)
170+
end function e
171+
end interface
172+
integer a(1), b(2,2)
173+
174+
forall (i=1:1)
175+
a(i) = e(b(:,i)) + 1
176+
end forall
177+
! CHECK: return
178+
! CHECK: }
179+
end subroutine embox_argument_with_slice

0 commit comments

Comments
 (0)