File tree Expand file tree Collapse file tree 2 files changed +18
-5
lines changed Expand file tree Collapse file tree 2 files changed +18
-5
lines changed Original file line number Diff line number Diff line change @@ -1348,7 +1348,7 @@ struct SymbolDependenceDepth {
1348
1348
llvm_unreachable (" not yet implemented - derived type analysis" );
1349
1349
1350
1350
// Symbol must be something lowering will have to allocate.
1351
- bool global = semantics::IsSaved (sym);
1351
+ bool global = lower::symbolIsGlobal (sym);
1352
1352
int depth = 0 ;
1353
1353
const auto *symTy = sym.GetType ();
1354
1354
assert (symTy && " symbol must have a type" );
@@ -1390,12 +1390,9 @@ struct SymbolDependenceDepth {
1390
1390
doExplicit (subs.ubound ());
1391
1391
}
1392
1392
// 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 ())
1396
1394
for (const auto &s : evaluate::CollectSymbols (*e))
1397
1395
depth = std::max (analyze (s) + 1 , depth);
1398
- }
1399
1396
}
1400
1397
adjustSize (depth + 1 );
1401
1398
vars[depth].emplace_back (sym, global, depth);
Original file line number Diff line number Diff line change @@ -316,3 +316,19 @@ subroutine issue857_char(rhs)
316
316
! CHECK: fir.store %[[len2]] to %[[lhs2_len]] : !fir.ref<index>
317
317
lhs2(1 :2 , 1 :25 ) = > rhs(1 :50 :1 )
318
318
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
You can’t perform that action at this time.
0 commit comments