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