Skip to content

Commit 51261bd

Browse files
authored
Process block data programs early (#1059)
Block data programs may initialize common block data, so process them in a preliminary pass (along with function declarations and module variables) to give them precedence over other common block declarations.
1 parent 90abadc commit 51261bd

File tree

4 files changed

+56
-84
lines changed

4 files changed

+56
-84
lines changed

flang/lib/Lower/Bridge.cpp

Lines changed: 28 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -106,34 +106,46 @@ using IncrementLoopNestInfo = llvm::SmallVector<IncrementLoopInfo>;
106106

107107
namespace {
108108

109-
/// Walk over the pre-FIR tree (PFT) and lower it to the FIR dialect of MLIR.
110-
///
111-
/// After building the PFT, the FirConverter processes that representation
112-
/// and lowers it to the FIR executable representation.
109+
/// Traverse the pre-FIR tree (PFT) to generate the FIR dialect of MLIR.
113110
class FirConverter : public Fortran::lower::AbstractConverter {
114111
public:
115112
explicit FirConverter(Fortran::lower::LoweringBridge &bridge)
116113
: bridge{bridge}, foldingContext{bridge.createFoldingContext()} {}
117114
virtual ~FirConverter() = default;
118115

119-
/// Convert the PFT to FIR
116+
/// Convert the PFT to FIR.
120117
void run(Fortran::lower::pft::Program &pft) {
121-
// Declare mlir::FuncOp for all the FunctionLikeUnit defined in the PFT
122-
// before lowering any function bodies so that the definition signatures
123-
// prevail on call spot signatures.
124-
declareFunctions(pft);
125-
126-
// Define variables of the modules defined in this program. This is done
127-
// first to ensure they are defined before lowering any function that may
128-
// use them.
129-
lowerModuleVariables(pft);
130-
// do translation
118+
// Preliminary translation pass.
119+
// - Declare all functions that have definitions so that definition
120+
// signatures prevail over call site signatures.
121+
// - Define module variables so they are available before lowering any
122+
// function that may use them.
123+
// - Translate block data programs so that common block definitions with
124+
// data initializations take precedence over other definitions.
125+
for (auto &u : pft.getUnits()) {
126+
std::visit(
127+
Fortran::common::visitors{
128+
[&](Fortran::lower::pft::FunctionLikeUnit &f) {
129+
declareFunction(f);
130+
},
131+
[&](Fortran::lower::pft::ModuleLikeUnit &m) {
132+
lowerModuleVariables(m);
133+
for (auto &f : m.nestedFunctions)
134+
declareFunction(f);
135+
},
136+
[&](Fortran::lower::pft::BlockDataUnit &b) { lowerBlockData(b); },
137+
[&](Fortran::lower::pft::CompilerDirectiveUnit &d) {},
138+
},
139+
u);
140+
}
141+
142+
// Primary translation pass.
131143
for (auto &u : pft.getUnits()) {
132144
std::visit(
133145
Fortran::common::visitors{
134146
[&](Fortran::lower::pft::FunctionLikeUnit &f) { lowerFunc(f); },
135147
[&](Fortran::lower::pft::ModuleLikeUnit &m) { lowerMod(m); },
136-
[&](Fortran::lower::pft::BlockDataUnit &b) { lowerBlockData(b); },
148+
[&](Fortran::lower::pft::BlockDataUnit &b) {},
137149
[&](Fortran::lower::pft::CompilerDirectiveUnit &d) {
138150
setCurrentPosition(
139151
d.get<Fortran::parser::CompilerDirective>().source);
@@ -145,29 +157,6 @@ class FirConverter : public Fortran::lower::AbstractConverter {
145157
}
146158
}
147159

148-
/// Declare mlir::FuncOp for all the FunctionLikeUnit defined in the PFT
149-
/// without any other side-effects.
150-
void declareFunctions(Fortran::lower::pft::Program &pft) {
151-
for (auto &u : pft.getUnits()) {
152-
std::visit(Fortran::common::visitors{
153-
[&](Fortran::lower::pft::FunctionLikeUnit &f) {
154-
declareFunction(f);
155-
},
156-
[&](Fortran::lower::pft::ModuleLikeUnit &m) {
157-
for (auto &f : m.nestedFunctions)
158-
declareFunction(f);
159-
},
160-
[&](Fortran::lower::pft::BlockDataUnit &) {
161-
// No functions defined in block data.
162-
},
163-
[&](Fortran::lower::pft::CompilerDirectiveUnit &) {
164-
// No functions defined.
165-
},
166-
},
167-
u);
168-
}
169-
}
170-
171160
/// Declare a function.
172161
void declareFunction(Fortran::lower::pft::FunctionLikeUnit &funit) {
173162
setCurrentPosition(funit.getStartingSourceLoc());
@@ -228,22 +217,6 @@ class FirConverter : public Fortran::lower::AbstractConverter {
228217
}
229218
}
230219

231-
/// Loop through modules defined in this file to generate the fir::globalOp
232-
/// for module variables.
233-
void lowerModuleVariables(Fortran::lower::pft::Program &pft) {
234-
for (auto &u : pft.getUnits()) {
235-
std::visit(Fortran::common::visitors{
236-
[&](Fortran::lower::pft::ModuleLikeUnit &m) {
237-
lowerModuleVariables(m);
238-
},
239-
[](auto &) {
240-
// Not a module, so no processing needed here.
241-
},
242-
},
243-
u);
244-
}
245-
}
246-
247220
//===--------------------------------------------------------------------===//
248221
// AbstractConverter overrides
249222
//===--------------------------------------------------------------------===//

flang/test/Lower/allocatable-globals.f90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,12 @@
33

44
! Test global allocatable definition lowering
55

6+
! CHECK-LABEL: fir.global linkonce @_QMmod_allocatablesEc : !fir.box<!fir.heap<!fir.array<?x!fir.char<1,10>>>> {
7+
! CHECK-DAG: %[[modcNullAddr:.*]] = fir.zero_bits !fir.heap<!fir.array<?x!fir.char<1,10>>>
8+
! CHECK-DAG: %[[modcShape:.*]] = fir.shape %c0{{.*}} : (index) -> !fir.shape<1>
9+
! CHECK: %[[modcInitBox:.*]] = fir.embox %[[modcNullAddr]](%[[modcShape]]) : (!fir.heap<!fir.array<?x!fir.char<1,10>>>, !fir.shape<1>) -> !fir.box<!fir.heap<!fir.array<?x!fir.char<1,10>>>>
10+
! CHECK: fir.has_value %[[modcInitBox]] : !fir.box<!fir.heap<!fir.array<?x!fir.char<1,10>>>>
11+
612
module mod_allocatables
713
character(10), allocatable :: c(:)
814
end module
@@ -32,12 +38,6 @@ subroutine test_globals()
3238
allocate(character(15):: gc1, gc2(60, 70))
3339
end subroutine
3440

35-
! CHECK-LABEL: fir.global linkonce @_QMmod_allocatablesEc : !fir.box<!fir.heap<!fir.array<?x!fir.char<1,10>>>> {
36-
! CHECK-DAG: %[[modcNullAddr:.*]] = fir.zero_bits !fir.heap<!fir.array<?x!fir.char<1,10>>>
37-
! CHECK-DAG: %[[modcShape:.*]] = fir.shape %c0{{.*}} : (index) -> !fir.shape<1>
38-
! CHECK: %[[modcInitBox:.*]] = fir.embox %[[modcNullAddr]](%[[modcShape]]) : (!fir.heap<!fir.array<?x!fir.char<1,10>>>, !fir.shape<1>) -> !fir.box<!fir.heap<!fir.array<?x!fir.char<1,10>>>>
39-
! CHECK: fir.has_value %[[modcInitBox]] : !fir.box<!fir.heap<!fir.array<?x!fir.char<1,10>>>>
40-
4141
! CHECK-LABEL: fir.global internal @_QFtest_globalsEgc1 : !fir.box<!fir.heap<!fir.char<1,?>>>
4242
! CHECK-DAG: %[[gc1NullAddr:.*]] = fir.zero_bits !fir.heap<!fir.char<1,?>>
4343
! CHECK: %[[gc1InitBox:.*]] = fir.embox %[[gc1NullAddr]] typeparams %c0{{.*}} : (!fir.heap<!fir.char<1,?>>, index) -> !fir.box<!fir.heap<!fir.char<1,?>>>

flang/test/Lower/array-constructor-1.f90

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module units
55
contains
66
! CHECK-LABEL: _QMunitsPis_preconnected_unit
77
logical function is_preconnected_unit(u)
8-
! CHECK: [[units_ssa:%[0-9]+]] = fir.address_of([[units_value:.*]]) : !fir.ref<!fir.array<3xi32>>
8+
! CHECK: [[units_ssa:%[0-9]+]] = fir.address_of(@_QMunitsECpreconnected_unit) : !fir.ref<!fir.array<3xi32>>
99
integer :: u
1010
integer :: i
1111
is_preconnected_unit = .true.
@@ -41,8 +41,6 @@ program prog
4141
call zero
4242
end
4343

44-
! CHECK: fir.global linkonce [[units_value]] constant : !fir.array<3xi32>
45-
4644
! CHECK: fir.global internal @_QFzeroECa constant : !fir.array<0x!fir.complex<4>>
4745
! CHECK: %0 = fir.undefined !fir.array<0x!fir.complex<4>>
4846
! CHECK: fir.has_value %0 : !fir.array<0x!fir.complex<4>>

flang/test/Lower/array.f90

Lines changed: 21 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,6 @@ subroutine s(i,j,k,ii,jj,kk,a1,a2,a3,a4,a5,a6,a7)
1414
integer a6(6:i,j:*)
1515
real a7(i:70,7:j,k:80)
1616

17-
1817
! CHECK-LABEL: BeginExternalListOutput
1918
! CHECK-DAG: fir.load %arg3 :
2019
! CHECK-DAG: %[[i1:.*]] = subi %{{.*}}, %[[one:c1.*]] :
@@ -76,6 +75,27 @@ subroutine s(i,j,k,ii,jj,kk,a1,a2,a3,a4,a5,a6,a7)
7675

7776
end subroutine s
7877

78+
! CHECK-LABEL: fir.global @_QBblock
79+
! CHECK: %[[VAL_1:.*]] = constant 1.000000e+00 : f32
80+
! CHECK: %[[VAL_2:.*]] = constant 2.400000e+00 : f32
81+
! CHECK: %[[VAL_3:.*]] = constant 0.000000e+00 : f32
82+
! CHECK: %[[VAL_4:.*]] = fir.undefined tuple<!fir.array<5x5xf32>>
83+
! CHECK: %[[VAL_5:.*]] = fir.undefined !fir.array<5x5xf32>
84+
! CHECK: %[[VAL_6:.*]] = fir.insert_on_range %[[VAL_5]], %[[VAL_1]], [0 : index, 1 : index, 0 : index, 0 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
85+
! CHECK: %[[VAL_7:.*]] = fir.insert_on_range %[[VAL_6]], %[[VAL_3]], [2 : index, 4 : index, 0 : index, 0 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
86+
! CHECK: %[[VAL_8:.*]] = fir.insert_on_range %[[VAL_7]], %[[VAL_1]], [0 : index, 1 : index, 1 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
87+
! CHECK: %[[VAL_9:.*]] = fir.insert_value %[[VAL_8]], %[[VAL_3]], [2 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
88+
! CHECK: %[[VAL_10:.*]] = fir.insert_value %[[VAL_9]], %[[VAL_2]], [3 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
89+
! CHECK: %[[VAL_11:.*]] = fir.insert_value %[[VAL_10]], %[[VAL_3]], [4 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
90+
! CHECK: %[[VAL_12:.*]] = fir.insert_on_range %[[VAL_11]], %[[VAL_1]], [0 : index, 1 : index, 2 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
91+
! CHECK: %[[VAL_13:.*]] = fir.insert_value %[[VAL_12]], %[[VAL_3]], [2 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
92+
! CHECK: %[[VAL_14:.*]] = fir.insert_value %[[VAL_13]], %[[VAL_2]], [3 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
93+
! CHECK: %[[VAL_15:.*]] = fir.insert_on_range %[[VAL_14]], %[[VAL_3]], [4 : index, 2 : index, 2 : index, 3 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
94+
! CHECK: %[[VAL_16:.*]] = fir.insert_value %[[VAL_15]], %[[VAL_2]], [3 : index, 3 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
95+
! CHECK: %[[VAL_17:.*]] = fir.insert_on_range %[[VAL_16]], %[[VAL_3]], [4 : index, 4 : index, 3 : index, 4 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
96+
! CHECK: %[[VAL_18:.*]] = fir.insert_value %[[VAL_4]], %[[VAL_17]], [0 : index] : (tuple<!fir.array<5x5xf32>>, !fir.array<5x5xf32>) -> tuple<!fir.array<5x5xf32>>
97+
! CHECK: fir.has_value %[[VAL_18]] : tuple<!fir.array<5x5xf32>>
98+
7999
! CHECK-LABEL range
80100
subroutine range()
81101
! Compile-time initalized arrays
@@ -129,25 +149,6 @@ subroutine rangeGlobal()
129149
end subroutine rangeGlobal
130150

131151
block data
132-
! CHECK: %[[VAL_223:.*]] = constant 1.000000e+00 : f32
133-
! CHECK: %[[VAL_224:.*]] = constant 2.400000e+00 : f32
134-
! CHECK: %[[VAL_225:.*]] = constant 0.000000e+00 : f32
135-
! CHECK: %[[VAL_226:.*]] = fir.undefined tuple<!fir.array<5x5xf32>>
136-
! CHECK: %[[VAL_227:.*]] = fir.undefined !fir.array<5x5xf32>
137-
! CHECK: %[[VAL_228:.*]] = fir.insert_on_range %[[VAL_227]], %[[VAL_223]], [0 : index, 1 : index, 0 : index, 0 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
138-
! CHECK: %[[VAL_229:.*]] = fir.insert_on_range %[[VAL_228]], %[[VAL_225]], [2 : index, 4 : index, 0 : index, 0 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
139-
! CHECK: %[[VAL_230:.*]] = fir.insert_on_range %[[VAL_229]], %[[VAL_223]], [0 : index, 1 : index, 1 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
140-
! CHECK: %[[VAL_231:.*]] = fir.insert_value %[[VAL_230]], %[[VAL_225]], [2 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
141-
! CHECK: %[[VAL_232:.*]] = fir.insert_value %[[VAL_231]], %[[VAL_224]], [3 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
142-
! CHECK: %[[VAL_233:.*]] = fir.insert_value %[[VAL_232]], %[[VAL_225]], [4 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
143-
! CHECK: %[[VAL_234:.*]] = fir.insert_on_range %[[VAL_233]], %[[VAL_223]], [0 : index, 1 : index, 2 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
144-
! CHECK: %[[VAL_235:.*]] = fir.insert_value %[[VAL_234]], %[[VAL_225]], [2 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
145-
! CHECK: %[[VAL_236:.*]] = fir.insert_value %[[VAL_235]], %[[VAL_224]], [3 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
146-
! CHECK: %[[VAL_237:.*]] = fir.insert_on_range %[[VAL_236]], %[[VAL_225]], [4 : index, 2 : index, 2 : index, 3 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
147-
! CHECK: %[[VAL_238:.*]] = fir.insert_value %[[VAL_237]], %[[VAL_224]], [3 : index, 3 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
148-
! CHECK: %[[VAL_239:.*]] = fir.insert_on_range %[[VAL_238]], %[[VAL_225]], [4 : index, 4 : index, 3 : index, 4 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
149-
! CHECK: %[[VAL_240:.*]] = fir.insert_value %[[VAL_226]], %[[VAL_239]], [0 : index] : (tuple<!fir.array<5x5xf32>>, !fir.array<5x5xf32>) -> tuple<!fir.array<5x5xf32>>
150-
! CHECK: fir.has_value %[[VAL_240]] : tuple<!fir.array<5x5xf32>>
151152
real(selected_real_kind(6)) :: x(5,5)
152153
common /block/ x
153154
data x(1,1), x(2,1), x(3,1) / 1, 1, 0 /

0 commit comments

Comments
 (0)