1 ! RUN: %python %S/test_symbols.py %s %flang_fc1
2 !DEF: /s1 (Subroutine) Subprogram
4 !DEF: /s1/a ObjectEntity REAL(4)
5 !DEF: /s1/b ObjectEntity REAL(4)
7 !DEF: /s1/i ObjectEntity INTEGER(8)
9 !DEF: /s1/Forall1/i ObjectEntity INTEGER(8)
16 !DEF: /s1/Forall2/i ObjectEntity INTEGER(8)
19 forall(i
=1:10)a(i
) = b(i
)
22 !DEF: /s2 (Subroutine) Subprogram
24 !DEF: /s2/a ObjectEntity REAL(4)
26 !DEF: /s2/i ObjectEntity INTEGER(4)
28 !DEF: /s2/OtherConstruct1/i ObjectEntity INTEGER(4)
31 !REF: /s2/OtherConstruct1/i
42 !DEF: /s3 (Subroutine) Subprogram
44 !DEF: /s3/n PARAMETER ObjectEntity INTEGER(4)
45 integer, parameter :: n
= 4
46 !DEF: /s3/n2 PARAMETER ObjectEntity INTEGER(4)
48 integer, parameter :: n2
= n
*n
50 !DEF: /s3/x (InDataStmt) ObjectEntity REAL(4)
51 real, dimension(n
,n
) :: x
53 !DEF: /s3/ImpliedDos1/k (Implicit) ObjectEntity INTEGER(4)
54 !DEF: /s3/ImpliedDos1/j ObjectEntity INTEGER(8)
57 data ((x(k
,j
),integer(kind
=8)::j
=1,n
),k
=1,n
)/n2
*3.0/
60 !DEF: /s4 (Subroutine) Subprogram
62 !DEF: /s4/t DerivedType
63 !DEF: /s4/t/k TypeParam INTEGER(4)
67 !DEF: /s4/t/a ObjectEntity INTEGER(4)
71 !DEF: /s4/x (InDataStmt) ObjectEntity TYPE(t(k=1_4))
81 !DEF: /s5 (Subroutine) Subprogram
83 !DEF: /s5/t DerivedType
84 !DEF: /s5/t/l TypeParam INTEGER(4)
90 !DEF: /s5/x ALLOCATABLE ObjectEntity TYPE(t(l=:))
91 type(t(:)), allocatable
:: x
92 !DEF: /s5/y ALLOCATABLE ObjectEntity REAL(4)
93 real, allocatable
:: y
101 !DEF: /s6 (Subroutine) Subprogram
103 !DEF: /s6/j ObjectEntity INTEGER(8)
105 !DEF: /s6/a ObjectEntity INTEGER(4)
107 !DEF: /s6/OtherConstruct1/i ObjectEntity INTEGER(4)
108 !DEF: /s6/OtherConstruct1/j (LocalityLocal) HostAssoc INTEGER(8)
109 !DEF: /s6/OtherConstruct1/k (Implicit, LocalityLocalInit) HostAssoc INTEGER(4)
110 !DEF: /s6/OtherConstruct1/a (LocalityShared) HostAssoc INTEGER(4)
111 do concurrent(integer::i
=1:5)local(j
)local_init(k
)shared(a
)
112 !REF: /s6/OtherConstruct1/a
113 !REF: /s6/OtherConstruct1/i
114 !REF: /s6/OtherConstruct1/j
119 !DEF: /s7 (Subroutine) Subprogram
121 !DEF: /s7/one PARAMETER ObjectEntity REAL(4)
122 real, parameter :: one
= 1.0
123 !DEF: /s7/z ObjectEntity COMPLEX(4)
125 complex :: z
= (one
, -one
)
128 !DEF: /s8 (Subroutine) Subprogram
130 !DEF: /s8/one PARAMETER ObjectEntity REAL(4)
131 real, parameter :: one
= 1.0
132 !DEF: /s8/y (InDataStmt) ObjectEntity REAL(4)
133 !DEF: /s8/z (InDataStmt) ObjectEntity REAL(4)
136 !DEF: /s8/ImpliedDos1/i (Implicit) ObjectEntity INTEGER(4)
138 !DEF: /s8/ImpliedDos2/i (Implicit) ObjectEntity INTEGER(4)
139 !DEF: /s8/x (Implicit, InDataStmt) ObjectEntity REAL(4)
141 data (y(i
),i
=1,10),(z(i
),i
=1,10),x
/21*one
/