xref: /llvm-project/flang/test/Semantics/symbol09.f90 (revision 90828d67ea35c86b76fc8f3dec5da03f645eadaf)
1! RUN: %python %S/test_symbols.py %s %flang_fc1
2!DEF: /s1 (Subroutine) Subprogram
3subroutine s1
4 !DEF: /s1/a ObjectEntity REAL(4)
5 !DEF: /s1/b ObjectEntity REAL(4)
6 real a(10), b(10)
7 !DEF: /s1/i ObjectEntity INTEGER(8)
8 integer(kind=8) i
9 !DEF: /s1/Forall1/i ObjectEntity INTEGER(8)
10 forall(i=1:10)
11  !REF: /s1/a
12  !REF: /s1/Forall1/i
13  !REF: /s1/b
14  a(i) = b(i)
15 end forall
16 !DEF: /s1/Forall2/i ObjectEntity INTEGER(8)
17 !REF: /s1/a
18 !REF: /s1/b
19 forall(i=1:10)a(i) = b(i)
20end subroutine
21
22!DEF: /s2 (Subroutine) Subprogram
23subroutine s2
24 !DEF: /s2/a ObjectEntity REAL(4)
25 real a(10)
26 !DEF: /s2/i ObjectEntity INTEGER(4)
27 integer i
28 !DEF: /s2/Forall1/i ObjectEntity INTEGER(4)
29 do concurrent(i=1:10)
30  !REF: /s2/a
31  !REF: /s2/Forall1/i
32  a(i) = i
33 end do
34 !REF: /s2/i
35 do i=1,10
36  !REF: /s2/a
37  !REF: /s2/i
38  a(i) = i
39 end do
40end subroutine
41
42!DEF: /s3 (Subroutine) Subprogram
43subroutine s3
44 !DEF: /s3/n PARAMETER ObjectEntity INTEGER(4)
45 integer, parameter :: n = 4
46 !DEF: /s3/n2 PARAMETER ObjectEntity INTEGER(4)
47 !REF: /s3/n
48 integer, parameter :: n2 = n*n
49 !REF: /s3/n
50 !DEF: /s3/x (InDataStmt) ObjectEntity REAL(4)
51 real, dimension(n,n) :: x
52 !REF: /s3/x
53 !DEF: /s3/ImpliedDos1/k (Implicit) ObjectEntity INTEGER(4)
54 !DEF: /s3/ImpliedDos1/j ObjectEntity INTEGER(8)
55 !REF: /s3/n
56 !REF: /s3/n2
57 data ((x(k,j),integer(kind=8)::j=1,n),k=1,n)/n2*3.0/
58end subroutine
59
60!DEF: /s4 (Subroutine) Subprogram
61subroutine s4
62 !DEF: /s4/t DerivedType
63 !DEF: /s4/t/k TypeParam INTEGER(4)
64 type :: t(k)
65  !REF: /s4/t/k
66  integer, kind :: k
67  !DEF: /s4/t/a ObjectEntity INTEGER(4)
68  integer :: a
69 end type t
70 !REF: /s4/t
71 !DEF: /s4/x (InDataStmt) ObjectEntity TYPE(t(k=1_4))
72 type(t(1)) :: x
73 !REF: /s4/x
74 !REF: /s4/t
75 data x/t(1)(2)/
76 !REF: /s4/x
77 !REF: /s4/t
78 x = t(1)(2)
79end subroutine
80
81!DEF: /s5 (Subroutine) Subprogram
82subroutine s5
83 !DEF: /s5/t DerivedType
84 !DEF: /s5/t/l TypeParam INTEGER(4)
85 type :: t(l)
86  !REF: /s5/t/l
87  integer, len :: l
88 end type t
89 !REF: /s5/t
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
94 !REF: /s5/t
95 !REF: /s5/x
96 allocate(t(1)::x)
97 !REF: /s5/y
98 allocate(real::y)
99end subroutine
100
101!DEF: /s6 (Subroutine) Subprogram
102subroutine s6
103 !DEF: /s6/j ObjectEntity INTEGER(8)
104 integer(kind=8) j
105 !DEF: /s6/a ObjectEntity INTEGER(4)
106 integer :: a(5) = 1
107 !DEF: /s6/Forall1/i ObjectEntity INTEGER(4)
108 !DEF: /s6/Forall1/j (LocalityLocal) HostAssoc INTEGER(8)
109 !DEF: /s6/Forall1/k (Implicit, LocalityLocalInit) HostAssoc INTEGER(4)
110 !DEF: /s6/Forall1/a (LocalityShared) HostAssoc INTEGER(4)
111 do concurrent(integer::i=1:5)local(j)local_init(k)shared(a)
112  !REF: /s6/Forall1/a
113  !REF: /s6/Forall1/i
114  !REF: /s6/Forall1/j
115  a(i) = j+1
116 end do
117end subroutine
118
119!DEF: /s7 (Subroutine) Subprogram
120subroutine s7
121 !DEF: /s7/one PARAMETER ObjectEntity REAL(4)
122 real, parameter :: one = 1.0
123 !DEF: /s7/z ObjectEntity COMPLEX(4)
124 !REF: /s7/one
125 complex :: z = (one, -one)
126end subroutine
127
128!DEF: /s8 (Subroutine) Subprogram
129subroutine s8
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)
134 real y(10), z(10)
135 !REF: /s8/y
136 !DEF: /s8/ImpliedDos1/i (Implicit) ObjectEntity INTEGER(4)
137 !REF: /s8/z
138 !DEF: /s8/ImpliedDos2/i (Implicit) ObjectEntity INTEGER(4)
139 !DEF: /s8/x (Implicit, InDataStmt) ObjectEntity REAL(4)
140 !REF: /s8/one
141 data (y(i),i=1,10),(z(i),i=1,10),x/21*one/
142end subroutine
143