Skip to content

Commit ffdceed

Browse files
[OpenMP] Fix assertion when array slice is passed as an argument in parallel
1 parent a6f3a74 commit ffdceed

File tree

2 files changed

+80
-2
lines changed

2 files changed

+80
-2
lines changed

flang/lib/Optimizer/CodeGen/CodeGen.cpp

Lines changed: 16 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -983,8 +983,22 @@ struct EmboxCommonConversion : public FIROpConversion<OP> {
983983
mlir::ConversionPatternRewriter &rewriter) const {
984984
auto thisPt = rewriter.saveInsertionPoint();
985985
auto *thisBlock = rewriter.getInsertionBlock();
986-
auto func = mlir::cast<mlir::LLVM::LLVMFuncOp>(thisBlock->getParentOp());
987-
rewriter.setInsertionPointToStart(&func.front());
986+
auto op = thisBlock->getParentOp();
987+
// Order to find the Op in whose entry block the alloca should be inserted.
988+
// The parent Op if it is an LLVM Function Op.
989+
// The ancestor OpenMP Op which is outlineable.
990+
// The ancestor LLVM Function Op.
991+
if (auto iface =
992+
thisBlock->getParent()
993+
->getParentOfType<
994+
mlir::omp::OutlineableOpenMPOpInterface>()) {
995+
rewriter.setInsertionPointToStart(iface.getAllocaBlock());
996+
} else {
997+
auto func = mlir::isa<mlir::LLVM::LLVMFuncOp>(op) ?
998+
mlir::cast<mlir::LLVM::LLVMFuncOp>(op) :
999+
op->getParentOfType<mlir::LLVM::LLVMFuncOp>();
1000+
rewriter.setInsertionPointToStart(&func.front());
1001+
}
9881002
auto sz = this->genConstantOffset(loc, rewriter, 1);
9891003
auto al = rewriter.create<mlir::LLVM::AllocaOp>(loc, toTy, sz, alignment);
9901004
rewriter.restoreInsertionPoint(thisPt);
Lines changed: 64 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,64 @@
1+
! This test checks passing an array slice in a parallel region
2+
3+
! RUN: bbc -fopenmp %s -o - | tco 2>&1 | FileCheck %s
4+
5+
! CHECK-LABEL: @_QPsb1..omp_par
6+
! CHECK-LABEL: omp.par.region1
7+
! CHECK: %[[SB1_MAT:.*]] = alloca { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }, align 8
8+
! CHECK: %[[SB1_MAT1:.*]] = getelementptr { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }, { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }* %[[SB1_MAT]], i32 0, i32 0
9+
! CHECK: %[[SB1_MAT2:.*]] = load i32*, i32** %[[SB1_MAT1]], align 8
10+
! CHECK: %[[SB1_MAT3:.*]] = bitcast i32* %[[SB1_MAT2]] to [3 x i32]*
11+
! CHECK: call void @_QPouter_src_calc([3 x i32]* %[[SB1_MAT3]])
12+
13+
subroutine sb1
14+
IMPLICIT NONE
15+
INTEGER, DIMENSION(3, 3) :: mat
16+
INTEGER :: k
17+
18+
!$OMP PARALLEL
19+
DO k = 1, 2
20+
CALL outer_src_calc ( mat(:,k) )
21+
END DO
22+
!$OMP END PARALLEL
23+
end subroutine
24+
25+
! CHECK-LABEL: @_QPsb2..omp_par
26+
! CHECK-LABEL: omp.par.region1
27+
! CHECK: %[[SB2_MAT:.*]] = alloca { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }, align 8
28+
! CHECK: call i32 @__kmpc_master
29+
! CHECK: %[[SB2_MAT1:.*]] = getelementptr { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }, { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }* %[[SB2_MAT]], i32 0, i32 0
30+
! CHECK: %[[SB2_MAT2:.*]] = load i32*, i32** %[[SB2_MAT1]], align 8
31+
! CHECK: %[[SB2_MAT3:.*]] = bitcast i32* %[[SB2_MAT2]] to [3 x i32]*
32+
! CHECK: call void @_QPouter_src_calc([3 x i32]* %[[SB2_MAT3]])
33+
subroutine sb2
34+
IMPLICIT NONE
35+
INTEGER, DIMENSION(3, 3) :: mat
36+
INTEGER :: k
37+
38+
!$OMP PARALLEL
39+
!$OMP MASTER
40+
DO k = 1, 2
41+
CALL outer_src_calc ( mat(:,k) )
42+
END DO
43+
!$OMP END MASTER
44+
!$OMP END PARALLEL
45+
end subroutine
46+
47+
! CHECK-LABEL: @_QPsb3
48+
! CHECK: %[[SB3_MAT:.*]] = alloca { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }, align 8
49+
! CHECK: call i32 @__kmpc_master
50+
! CHECK: %[[SB3_MAT1:.*]] = getelementptr { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }, { i32*, i64, i32, i8, i8, i8, i8, [1 x [3 x i64]] }* %[[SB3_MAT]], i32 0, i32 0
51+
! CHECK: %[[SB3_MAT2:.*]] = load i32*, i32** %[[SB3_MAT1]], align 8
52+
! CHECK: %[[SB3_MAT3:.*]] = bitcast i32* %[[SB3_MAT2]] to [3 x i32]*
53+
! CHECK: call void @_QPouter_src_calc([3 x i32]* %[[SB3_MAT3]])
54+
subroutine sb3
55+
IMPLICIT NONE
56+
INTEGER, DIMENSION(3, 3) :: mat
57+
INTEGER :: k
58+
59+
!$OMP MASTER
60+
DO k = 1, 2
61+
CALL outer_src_calc ( mat(:,k) )
62+
END DO
63+
!$OMP END MASTER
64+
end subroutine

0 commit comments

Comments
 (0)