Skip to content

Commit 6bc4946

Browse files
committed
[flang] handle allocatable components when creating array temps
When creating an array temporary in the array copy pass, care must be taken with allocatable components. The element components needs to be given a clean unallocated status before being used in the assignments. This is because assignment of allocatable components makes deep copy, and may cause deallocation of the previous value if it was allocated. Hence the previous allocation status cannot be let undefined. On top of that, when cleaning-up the temp, all allocatable components that may have been allocated must be deallocated. This patch implements this by centralizing the code making and cleaning array temps in ArrayValueCopy.cpp, and by calling Initialize and Destroy runtime entry points to deal when they are allocatable components.
1 parent 2237e33 commit 6bc4946

File tree

2 files changed

+107
-12
lines changed

2 files changed

+107
-12
lines changed

flang/lib/Optimizer/Transforms/ArrayValueCopy.cpp

Lines changed: 52 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@
1313
#include "flang/Optimizer/Builder/Character.h"
1414
#include "flang/Optimizer/Builder/FIRBuilder.h"
1515
#include "flang/Optimizer/Builder/Factory.h"
16+
#include "flang/Optimizer/Builder/Runtime/Derived.h"
1617
#include "flang/Optimizer/Dialect/FIRDialect.h"
1718
#include "flang/Optimizer/Dialect/FIROpsSupport.h"
1819
#include "flang/Optimizer/Support/FIRContext.h"
@@ -999,6 +1000,50 @@ findNonconstantExtents(mlir::Type memrefTy,
9991000
return nce;
10001001
}
10011002

1003+
/// Allocate temporary storage for an ArrayLoadOp \load and initialize any
1004+
/// allocatable direct components of the array elements with an unallocated
1005+
/// status. Returns the temporary address as well as a callback to generate the
1006+
/// temporary clean-up once it has been used. The clean-up will take care of
1007+
/// deallocating all the element allocatable components that may have been
1008+
/// allocated while using the temporary.
1009+
static std::pair<mlir::Value,
1010+
std::function<void(mlir::PatternRewriter &rewriter)>>
1011+
allocateArrayTemp(mlir::Location loc, mlir::PatternRewriter &rewriter,
1012+
ArrayLoadOp load, llvm::ArrayRef<mlir::Value> extents,
1013+
mlir::Value shape) {
1014+
mlir::Type baseType = load.memref().getType();
1015+
llvm::SmallVector<mlir::Value> nonconstantExtents =
1016+
findNonconstantExtents(baseType, extents);
1017+
llvm::SmallVector<mlir::Value> typeParams =
1018+
genArrayLoadTypeParameters(loc, rewriter, load);
1019+
mlir::Value allocmem = rewriter.create<AllocMemOp>(
1020+
loc, dyn_cast_ptrOrBoxEleTy(baseType), typeParams, nonconstantExtents);
1021+
mlir::Type eleType =
1022+
fir::unwrapSequenceType(fir::unwrapPassByRefType(baseType));
1023+
if (fir::isRecordWithAllocatableMember(eleType)) {
1024+
// The allocatable component descriptors need to be set to a clean
1025+
// deallocated status before anything is done with them.
1026+
mlir::Value box = rewriter.create<fir::EmboxOp>(
1027+
loc, fir::BoxType::get(baseType), allocmem, shape,
1028+
/*slice=*/mlir::Value{}, typeParams);
1029+
auto module = load->getParentOfType<mlir::ModuleOp>();
1030+
FirOpBuilder builder(rewriter, getKindMapping(module));
1031+
runtime::genDerivedTypeInitialize(builder, loc, box);
1032+
// Any allocatable component that may have been allocated must be
1033+
// deallocated during the clean-up.
1034+
auto cleanup = [=](mlir::PatternRewriter &r) {
1035+
FirOpBuilder builder(r, getKindMapping(module));
1036+
runtime::genDerivedTypeDestroy(builder, loc, box);
1037+
r.create<FreeMemOp>(loc, allocmem);
1038+
};
1039+
return {allocmem, cleanup};
1040+
}
1041+
auto cleanup = [=](mlir::PatternRewriter &r) {
1042+
r.create<FreeMemOp>(loc, allocmem);
1043+
};
1044+
return {allocmem, cleanup};
1045+
}
1046+
10021047
namespace {
10031048
/// Conversion of fir.array_update and fir.array_modify Ops.
10041049
/// If there is a conflict for the update, then we need to perform a
@@ -1030,11 +1075,8 @@ class ArrayUpdateConversionBase : public mlir::OpRewritePattern<ArrayOp> {
10301075
bool copyUsingSlice = false;
10311076
auto shapeOp = getOrReadExtentsAndShapeOp(loc, rewriter, load, extents,
10321077
copyUsingSlice);
1033-
llvm::SmallVector<mlir::Value> nonconstantExtents =
1034-
findNonconstantExtents(load.memref().getType(), extents);
1035-
auto allocmem = rewriter.create<AllocMemOp>(
1036-
loc, dyn_cast_ptrOrBoxEleTy(load.memref().getType()),
1037-
genArrayLoadTypeParameters(loc, rewriter, load), nonconstantExtents);
1078+
auto [allocmem, genTempCleanUp] =
1079+
allocateArrayTemp(loc, rewriter, load, extents, shapeOp);
10381080
genArrayCopy</*copyIn=*/true>(load.getLoc(), rewriter, allocmem,
10391081
load.memref(), shapeOp, load.slice(), load);
10401082
// Generate the reference for the access.
@@ -1050,7 +1092,7 @@ class ArrayUpdateConversionBase : public mlir::OpRewritePattern<ArrayOp> {
10501092
// Copy out.
10511093
genArrayCopy</*copyIn=*/false>(store.getLoc(), rewriter, store.memref(),
10521094
allocmem, shapeOp, store.slice(), load);
1053-
rewriter.create<FreeMemOp>(loc, allocmem);
1095+
genTempCleanUp(rewriter);
10541096
return coor;
10551097
}
10561098

@@ -1080,11 +1122,9 @@ class ArrayUpdateConversionBase : public mlir::OpRewritePattern<ArrayOp> {
10801122
bool copyUsingSlice = false;
10811123
auto shapeOp = getOrReadExtentsAndShapeOp(loc, rewriter, load, extents,
10821124
copyUsingSlice);
1083-
llvm::SmallVector<mlir::Value> nonconstantExtents =
1084-
findNonconstantExtents(load.memref().getType(), extents);
1085-
auto allocmem = rewriter.create<AllocMemOp>(
1086-
loc, dyn_cast_ptrOrBoxEleTy(load.memref().getType()),
1087-
genArrayLoadTypeParameters(loc, rewriter, load), nonconstantExtents);
1125+
auto [allocmem, genTempCleanUp] =
1126+
allocateArrayTemp(loc, rewriter, load, extents, shapeOp);
1127+
10881128
genArrayCopy</*copyIn=*/true>(load.getLoc(), rewriter, allocmem,
10891129
load.memref(), shapeOp, load.slice(), load);
10901130
rewriter.setInsertionPoint(op);
@@ -1100,7 +1140,7 @@ class ArrayUpdateConversionBase : public mlir::OpRewritePattern<ArrayOp> {
11001140
// Copy out.
11011141
genArrayCopy</*copyIn=*/false>(store.getLoc(), rewriter, store.memref(),
11021142
allocmem, shapeOp, store.slice(), load);
1103-
rewriter.create<FreeMemOp>(loc, allocmem);
1143+
genTempCleanUp(rewriter);
11041144
return {coor, load.getResult()};
11051145
}
11061146
// Otherwise, when there is no conflict (a possible loop-carried
Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,55 @@
1+
// Test overlapping assignment of derived type arrays with allocatable components.
2+
// This requires initializing the allocatable components to an unallocated status
3+
// before they can be used in component assignments, and to deallocate the components
4+
// that may have been allocated in the end.
5+
6+
// RUN: fir-opt --array-value-copy %s | FileCheck %s
7+
8+
9+
!t_with_alloc_comp = type !fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>
10+
func private @custom_assign(!fir.ref<!t_with_alloc_comp>, !fir.ref<!t_with_alloc_comp>)
11+
func @test_overlap_with_alloc_components(%arg0: !fir.ref<!fir.array<10x!t_with_alloc_comp>>) {
12+
%0 = fir.alloca !fir.box<!t_with_alloc_comp>
13+
%c10 = arith.constant 10 : index
14+
%c9 = arith.constant 9 : index
15+
%c1 = arith.constant 1 : index
16+
%c-1 = arith.constant -1 : index
17+
%c0 = arith.constant 0 : index
18+
%1 = fir.shape %c10 : (index) -> !fir.shape<1>
19+
%6 = fir.slice %c10, %c1, %c-1 : (index, index, index) -> !fir.slice<1>
20+
%2 = fir.array_load %arg0(%1) : (!fir.ref<!fir.array<10x!t_with_alloc_comp>>, !fir.shape<1>) -> !fir.array<10x!t_with_alloc_comp>
21+
%7 = fir.array_load %arg0(%1) [%6] : (!fir.ref<!fir.array<10x!t_with_alloc_comp>>, !fir.shape<1>, !fir.slice<1>) -> !fir.array<10x!t_with_alloc_comp>
22+
%9 = fir.do_loop %arg1 = %c0 to %c9 step %c1 unordered iter_args(%arg2 = %2) -> (!fir.array<10x!t_with_alloc_comp>) {
23+
%10 = fir.array_access %7, %arg1 : (!fir.array<10x!t_with_alloc_comp>, index) -> !fir.ref<!t_with_alloc_comp>
24+
%11 = fir.array_access %arg2, %arg1 : (!fir.array<10x!t_with_alloc_comp>, index) -> !fir.ref<!t_with_alloc_comp>
25+
fir.call @custom_assign(%11, %10) : (!fir.ref<!t_with_alloc_comp>, !fir.ref<!t_with_alloc_comp>) -> none
26+
%19 = fir.array_amend %arg2, %11 : (!fir.array<10x!t_with_alloc_comp>, !fir.ref<!t_with_alloc_comp>) -> !fir.array<10x!t_with_alloc_comp>
27+
fir.result %19 : !fir.array<10x!t_with_alloc_comp>
28+
}
29+
fir.array_merge_store %2, %9 to %arg0 : !fir.array<10x!t_with_alloc_comp>, !fir.array<10x!t_with_alloc_comp>, !fir.ref<!fir.array<10x!t_with_alloc_comp>>
30+
return
31+
}
32+
33+
// CHECK-LABEL: func @test_overlap_with_alloc_components(
34+
// CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<10x!fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>>>) {
35+
// CHECK: %[[VAL_4:.*]] = arith.constant 10 : index
36+
// CHECK: %[[VAL_6:.*]] = arith.constant 1 : index
37+
// CHECK: %[[VAL_7:.*]] = arith.constant -1 : index
38+
// CHECK: %[[VAL_9:.*]] = fir.shape %[[VAL_4]] : (index) -> !fir.shape<1>
39+
// CHECK: %[[VAL_10:.*]] = fir.slice %[[VAL_4]], %[[VAL_6]], %[[VAL_7]] : (index, index, index) -> !fir.slice<1>
40+
// CHECK: %[[VAL_11:.*]] = fir.allocmem !fir.array<10x!fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>>
41+
// CHECK: %[[VAL_12:.*]] = fir.embox %[[VAL_11]](%[[VAL_9]]) : (!fir.heap<!fir.array<10x!fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>>>, !fir.shape<1>) -> !fir.box<!fir.ref<!fir.array<10x!fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>>>>
42+
// CHECK: %[[VAL_16:.*]] = fir.convert %[[VAL_12]] : (!fir.box<!fir.ref<!fir.array<10x!fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>>>>) -> !fir.box<none>
43+
// CHECK: fir.call @_FortranAInitialize(%[[VAL_16]], %{{.*}}, %{{.*}}) : (!fir.box<none>, !fir.ref<i8>, i32) -> none
44+
// CHECK: fir.do_loop {{.*}} {
45+
// CHECK: fir.call @_FortranAAssign
46+
// CHECK: }
47+
// CHECK: fir.do_loop {{.*}} {
48+
// CHECK: fir.call @custom_assign
49+
// CHECK: }
50+
// CHECK: fir.do_loop %{{.*}} {
51+
// CHECK: fir.call @_FortranAAssign
52+
// CHECK: }
53+
// CHECK: %[[VAL_72:.*]] = fir.convert %[[VAL_12]] : (!fir.box<!fir.ref<!fir.array<10x!fir.type<t{i:!fir.box<!fir.heap<!fir.array<?xi32>>>}>>>>) -> !fir.box<none>
54+
// CHECK: %[[VAL_73:.*]] = fir.call @_FortranADestroy(%[[VAL_72]]) : (!fir.box<none>) -> none
55+
// CHECK: fir.freemem %[[VAL_11]]

0 commit comments

Comments
 (0)