Skip to content

Commit 51bc26f

Browse files
committed
[fix 1180] Ensure pft::Variable::isGlobal() is true for common block vars
1 parent c329c4f commit 51bc26f

File tree

2 files changed

+18
-5
lines changed

2 files changed

+18
-5
lines changed

flang/lib/Lower/PFTBuilder.cpp

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1348,7 +1348,7 @@ struct SymbolDependenceDepth {
13481348
llvm_unreachable("not yet implemented - derived type analysis");
13491349

13501350
// Symbol must be something lowering will have to allocate.
1351-
bool global = semantics::IsSaved(sym);
1351+
bool global = lower::symbolIsGlobal(sym);
13521352
int depth = 0;
13531353
const auto *symTy = sym.GetType();
13541354
assert(symTy && "symbol must have a type");
@@ -1390,12 +1390,9 @@ struct SymbolDependenceDepth {
13901390
doExplicit(subs.ubound());
13911391
}
13921392
// handle any symbols in initialization expressions
1393-
if (auto e = details->init()) {
1394-
// An object that is initialized is implicitly SAVE, so set the flag.
1395-
global = true;
1393+
if (auto e = details->init())
13961394
for (const auto &s : evaluate::CollectSymbols(*e))
13971395
depth = std::max(analyze(s) + 1, depth);
1398-
}
13991396
}
14001397
adjustSize(depth + 1);
14011398
vars[depth].emplace_back(sym, global, depth);

flang/test/Lower/pointer-assignments.f90

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -316,3 +316,19 @@ subroutine issue857_char(rhs)
316316
! CHECK: fir.store %[[len2]] to %[[lhs2_len]] : !fir.ref<index>
317317
lhs2(1:2, 1:25) => rhs(1:50:1)
318318
end subroutine
319+
320+
! CHECK-LABEL: func @_QPissue1180(
321+
! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<i32> {fir.target}) {
322+
subroutine issue1180(x)
323+
integer, target :: x
324+
integer, pointer :: p
325+
common /some_common/ p
326+
! CHECK: %[[VAL_1:.*]] = fir.address_of(@_QBsome_common) : !fir.ref<!fir.array<24xi8>>
327+
! CHECK: %[[VAL_2:.*]] = fir.convert %[[VAL_1]] : (!fir.ref<!fir.array<24xi8>>) -> !fir.ref<!fir.array<?xi8>>
328+
! CHECK: %[[VAL_3:.*]] = arith.constant 0 : index
329+
! CHECK: %[[VAL_4:.*]] = fir.coordinate_of %[[VAL_2]], %[[VAL_3]] : (!fir.ref<!fir.array<?xi8>>, index) -> !fir.ref<i8>
330+
! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_4]] : (!fir.ref<i8>) -> !fir.ref<!fir.box<!fir.ptr<i32>>>
331+
! CHECK: %[[VAL_6:.*]] = fir.embox %[[VAL_0]] : (!fir.ref<i32>) -> !fir.box<!fir.ptr<i32>>
332+
! CHECK: fir.store %[[VAL_6]] to %[[VAL_5]] : !fir.ref<!fir.box<!fir.ptr<i32>>>
333+
p => x
334+
end subroutine

0 commit comments

Comments
 (0)