xref: /llvm-project/flang/test/Semantics/data13.f90 (revision e7b8e18fc359c0de380e89b27898d18913ca9c50)
1! RUN: %flang_fc1 -fdebug-dump-symbols %s 2>&1 | FileCheck %s
2! Verify that the closure of EQUIVALENCE'd symbols with any DATA
3! initialization produces a combined initializer, with explicit
4! initialization overriding any default component initialization.
5! 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]
6! CHECK: ja, SAVE (InDataStmt) size=8 offset=0: ObjectEntity type: INTEGER(4) shape: 1_8:2_8
7! CHECK-NOT: x0, SAVE size=8 offset=8: ObjectEntity type: TYPE(t1) init:t1(m=123_4,n=234_4)
8! CHECK: x1 size=8 offset=16: ObjectEntity type: TYPE(t1) init:t1(m=345_4,n=234_4)
9! CHECK: x2, SAVE size=8 offset=0: ObjectEntity type: TYPE(t1)
10! CHECK-NOT: x3a, SAVE size=8 offset=24: ObjectEntity type: TYPE(t3) init:t3(t2=t2(k=567_4),j=0_4)
11! CHECK: x3b size=8 offset=32: ObjectEntity type: TYPE(t3) init:t3(k=567_4,j=678_4)
12! CHECK: Equivalence Sets: (x2,ja(1)) (.F18.0,x2)
13type :: t1
14  sequence
15  integer :: m = 123
16  integer :: n = 234
17end type
18type :: t2
19  integer :: k = 567
20end type
21type, extends(t2) :: t3
22  integer :: j ! uninitialized
23end type
24type(t1), save :: x0 ! not enabled
25type(t1) :: x1 = t1(m=345)
26type(t1) :: x2
27type(t3), save :: x3a ! not enabled
28type(t3) :: x3b = t3(j=678)
29integer :: ja(2)
30equivalence(x2, ja)
31data ja(1)/456/
32end
33