The combined initializers constructed from DATA statements and explicit static initialization in declarations needs to include derived type component default initializations, overriding those default values without complaint with values from explicit DATA statement or declaration initializations when they overlap. This also has to work for objects with storage association due to EQUIVALENCE. When storage association causes default component initializations to overlap, emit errors if and only if the values differ (See Fortran 2018 subclause 19.5.3, esp. paragraph 10). The f18 front-end has a module that analyzes and converts DATA statements into equivalent static initializers for objects. For storage-associated objects, compiler-generated objects are created that overlay the entire association and fill it with a combined initializer. This "data-to-inits" module already exists, and this patch is essentially extension and clean-up of its machinery to complete the job. Also: emit EQUIVALENCE to module files; mark compiler-created symbols and *don't* emit those to module files; check non-static EQUIVALENCE sets for conflicting default component initializations, so lowering doesn't have to check them or emit diagnostics. Differential Revision: https://reviews.llvm.org/D109022
33 lines
1.3 KiB
Fortran
33 lines
1.3 KiB
Fortran
! RUN: %flang_fc1 -fsyntax-only -fdebug-dump-symbols %s 2>&1 | FileCheck %s
|
|
! Verify that the closure of EQUIVALENCE'd symbols with any DATA
|
|
! initialization produces a combined initializer, with explicit
|
|
! initialization overriding any default component initialization.
|
|
! CHECK: .F18.0, SAVE (CompilerCreated) size=8 offset=0: ObjectEntity type: INTEGER(4) shape: 1_8:2_8 init:[INTEGER(4)::456_4,234_4]
|
|
! CHECK: ja (InDataStmt) size=8 offset=0: ObjectEntity type: INTEGER(4) shape: 1_8:2_8
|
|
! CHECK-NOT: x0, SAVE size=8 offset=8: ObjectEntity type: TYPE(t1) init:t1(m=123_4,n=234_4)
|
|
! CHECK: x1 size=8 offset=16: ObjectEntity type: TYPE(t1) init:t1(m=345_4,n=234_4)
|
|
! CHECK: x2 size=8 offset=0: ObjectEntity type: TYPE(t1)
|
|
! CHECK-NOT: x3a, SAVE size=8 offset=24: ObjectEntity type: TYPE(t3) init:t3(t2=t2(k=567_4),j=0_4)
|
|
! CHECK: x3b size=8 offset=32: ObjectEntity type: TYPE(t3) init:t3(k=567_4,j=678_4)
|
|
! CHECK: Equivalence Sets: (x2,ja(1)) (.F18.0,x2)
|
|
type :: t1
|
|
sequence
|
|
integer :: m = 123
|
|
integer :: n = 234
|
|
end type
|
|
type :: t2
|
|
integer :: k = 567
|
|
end type
|
|
type, extends(t2) :: t3
|
|
integer :: j ! uninitialized
|
|
end type
|
|
type(t1), save :: x0 ! not enabled
|
|
type(t1) :: x1 = t1(m=345)
|
|
type(t1) :: x2
|
|
type(t3), save :: x3a ! not enabled
|
|
type(t3) :: x3b = t3(j=678)
|
|
integer :: ja(2)
|
|
equivalence(x2, ja)
|
|
data ja(1)/456/
|
|
end
|