Skip to content

Commit 7001237

Browse files
authored
Don't put compiler generated objects in equivalence groups (#993)
Equivalence analysis has some problems that may be addressed by shifting the core analysis to the front end. Pending such changes, don't attempt to place compiler generated objects in any equivalence group.
1 parent df94154 commit 7001237

File tree

2 files changed

+32
-1
lines changed

2 files changed

+32
-1
lines changed

flang/lib/Lower/PFTBuilder.cpp

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1449,8 +1449,11 @@ struct SymbolDependenceDepth {
14491449
private:
14501450
/// Skip symbol in alias analysis.
14511451
bool skipSymbol(const semantics::Symbol &sym) {
1452+
// Common block equivalences are largely managed by the front end.
1453+
// Compiler generated symbols ('.' names) cannot be equivalenced.
1454+
// FIXME: Equivalence code generation may need to be revisited.
14521455
return !sym.has<semantics::ObjectEntityDetails>() ||
1453-
lower::definedInCommonBlock(sym);
1456+
lower::definedInCommonBlock(sym) || sym.name()[0] == '.';
14541457
}
14551458

14561459
// Make sure the table is of appropriate size.

flang/test/Lower/equivalence-1.f90

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -31,3 +31,31 @@ SUBROUTINE s2
3131
! CHECK: = fir.load %[[fld]] : !fir.ref<f32>
3232
PRINT *, r(3)
3333
END SUBROUTINE s2
34+
35+
! CHECK-LABEL: func @_QPs3
36+
SUBROUTINE s3
37+
REAL r(10)
38+
TYPE t
39+
SEQUENCE
40+
REAL r(10)
41+
END TYPE t
42+
TYPE(t) x
43+
! CHECK: %[[group:.*]] = fir.alloca !fir.array<40xi8>
44+
EQUIVALENCE (r,x)
45+
! CHECK: %[[coor:.*]] = fir.coordinate_of %[[group]], %c0 : (!fir.ref<!fir.array<40xi8>>, index) -> !fir.ref<i8>
46+
! CHECK: %[[rloc:.*]] = fir.convert %[[coor]] : (!fir.ref<i8>) -> !fir.ref<!fir.array<10xf32>>
47+
! CHECK: %[[xloc:.*]] = fir.convert %[[coor]] : (!fir.ref<i8>) -> !fir.ref<!fir.type<_QFs3Tt{r:!fir.array<10xf32>}>>
48+
! CHECK: %[[fidx:.*]] = fir.field_index r, !fir.type<_QFs3Tt{r:!fir.array<10xf32>}>
49+
! CHECK: %[[xrloc:.*]] = fir.coordinate_of %[[xloc]], %[[fidx]] :
50+
! CHECK: %[[v1loc:.*]] = fir.coordinate_of %[[xrloc]], %c8_i64 : (!fir.ref<!fir.array<10xf32>>, i64) -> !fir.ref<f32>
51+
! CHECK: fir.store %{{.*}} to %[[v1loc]] : !fir.ref<f32>
52+
x%r(9) = 9.0
53+
! CHECK: %[[v2loc:.*]] = fir.coordinate_of %[[rloc]], %c8_i64 : (!fir.ref<!fir.array<10xf32>>, i64) -> !fir.ref<f32>
54+
! CHECK: %{{.*}} = fir.load %[[v2loc]] : !fir.ref<f32>
55+
PRINT *, r(9)
56+
END SUBROUTINE s3
57+
58+
CALL s1
59+
CALL s2
60+
CALL s3
61+
END

0 commit comments

Comments
 (0)