mirror of
https://github.com/llvm/llvm-project.git
synced 2025-04-17 03:56:42 +00:00

Example: ``` subroutine global_sub() integer, dimension(4) :: iarr4=(/1,2,3,4/) integer, dimension(4) :: jarr4 equivalence(iarr4,jarr4) call sub1 print *, iarr4 contains subroutine sub1 iarr4=jarr4((/4:1:-1/)) end subroutine sub1 end subroutine global_sub ``` `iarr4` and `jarr4` are equivalenced via a global aggregate storage, but the references inside `sub1` are lowered differently. `iarr4` is accessed via the global aggregate storage, while `jarr4` is accessed via the argument tuple. This confuses the FIR alias analysis, that claims that a host associated entity cannot alias with a global (if they have different source and do not have Target/Pointer attributes deduced by the alias analysis). I am not convinced that there is an issue in the alias analysis yet. I think we'd better lower the accesses uniformly, i.e. if one variable from an equivalence is lowered via the global aggregate storage, then any other variable from this equivalence should be lowered the same way (even if they are used via host association). This patch makes sure that all symbols from an EQUIVALENCE get and implicit SAVE attribute, if they do not have it already and any symbol from the EQUIVALENCE is SAVEd (explicitly or implicitly). This makes the further lowering consistent.
46 lines
1.5 KiB
Fortran
46 lines
1.5 KiB
Fortran
! Check that symbols without SAVE attribute from an EQUIVALENCE
|
|
! with at least one symbol being SAVEd (explicitly or implicitly)
|
|
! have implicit SAVE attribute.
|
|
!RUN: %flang_fc1 -fdebug-dump-symbols %s | FileCheck %s
|
|
|
|
subroutine test1()
|
|
! CHECK-LABEL: Subprogram scope: test1
|
|
! CHECK: i1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4) init:1_4
|
|
! CHECK: j1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
integer :: i1 = 1
|
|
integer :: j1
|
|
equivalence(i1,j1)
|
|
end subroutine test1
|
|
|
|
subroutine test2()
|
|
! CHECK-LABEL: Subprogram scope: test2
|
|
! CHECK: i1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4) init:1_4
|
|
! CHECK: j1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
integer :: i1 = 1
|
|
integer :: j1
|
|
equivalence(j1,i1)
|
|
end subroutine test2
|
|
|
|
subroutine test3()
|
|
! CHECK-LABEL: Subprogram scope: test3
|
|
! CHECK: i1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
! CHECK: j1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
! CHECK: k1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
integer :: i1
|
|
integer :: j1, k1
|
|
common /blk/ k1
|
|
save /blk/
|
|
equivalence(i1,j1,k1)
|
|
end subroutine test3
|
|
|
|
subroutine test4()
|
|
! CHECK-LABEL: Subprogram scope: test4
|
|
! CHECK: i1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4) init:1_4
|
|
! CHECK: j1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
! CHECK: k1, SAVE size=4 offset=0: ObjectEntity type: INTEGER(4)
|
|
integer :: i1 = 1
|
|
integer :: j1, k1
|
|
common /blk/ k1
|
|
equivalence(i1,j1,k1)
|
|
end subroutine test4
|