Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / resolve35.f90
blob17034ebc2f0f351f5d99dedc3a0bc8d9c22b18d8
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Construct names
4 subroutine s1
5 real :: foo
6 !ERROR: 'foo' is already declared in this scoping unit
7 foo: block
8 end block foo
9 end
11 subroutine s2(x)
12 logical :: x
13 foo: if (x) then
14 end if foo
15 !ERROR: 'foo' is already declared in this scoping unit
16 foo: do i = 1, 10
17 end do foo
18 end
20 subroutine s3
21 real :: a(10,10), b(10,10)
22 type y; end type
23 integer(8) :: x
24 !ERROR: Index name 'y' conflicts with existing identifier
25 forall(x=1:10, y=1:10)
26 a(x, y) = b(x, y)
27 end forall
28 !ERROR: Index name 'y' conflicts with existing identifier
29 forall(x=1:10, y=1:10) a(x, y) = b(x, y)
30 end
32 subroutine s4
33 real :: a(10), b(10)
34 complex :: x
35 integer :: i(2)
36 !ERROR: Must have INTEGER type, but is COMPLEX(4)
37 forall(x=1:10)
38 !ERROR: Must have INTEGER type, but is COMPLEX(4)
39 !ERROR: Must have INTEGER type, but is COMPLEX(4)
40 a(x) = b(x)
41 end forall
42 !ERROR: Must have INTEGER type, but is REAL(4)
43 forall(y=1:10)
44 !ERROR: Must have INTEGER type, but is REAL(4)
45 !ERROR: Must have INTEGER type, but is REAL(4)
46 a(y) = b(y)
47 end forall
48 !ERROR: Index variable 'i' is not scalar
49 forall(i=1:10)
50 a(i) = b(i)
51 end forall
52 end
54 subroutine s6
55 integer, parameter :: n = 4
56 real, dimension(n) :: x
57 data(x(i), i=1, n) / n * 0.0 /
58 !ERROR: Index name 't' conflicts with existing identifier
59 forall(t=1:n) x(t) = 0.0
60 contains
61 subroutine t
62 end
63 end
65 subroutine s6b
66 integer, parameter :: k = 4
67 integer :: l = 4
68 forall(integer(k) :: i = 1:10)
69 end forall
70 ! C713 A scalar-int-constant-name shall be a named constant of type integer.
71 !ERROR: Must be a constant value
72 forall(integer(l) :: i = 1:10)
73 end forall
74 end
76 subroutine s7
77 !ERROR: 'i' is already declared in this scoping unit
78 do concurrent(integer::i=1:5) local(j, i) &
79 !ERROR: 'j' is already declared in this scoping unit
80 local_init(k, j) &
81 !WARNING: Variable 'a' with SHARED locality implicitly declared
82 shared(a)
83 a = j + 1
84 end do
85 end
87 subroutine s8
88 implicit none
89 !ERROR: No explicit type declared for 'i'
90 do concurrent(i=1:5) &
91 !ERROR: No explicit type declared for 'j'
92 local(j) &
93 !ERROR: No explicit type declared for 'k'
94 local_init(k)
95 end do
96 end
98 subroutine s9
99 integer :: j
100 !ERROR: 'i' is already declared in this scoping unit
101 do concurrent(integer::i=1:5) shared(i) &
102 shared(j) &
103 !ERROR: 'j' is already declared in this scoping unit
104 shared(j)
105 end do
108 subroutine s10
109 external bad1
110 real, parameter :: bad2 = 1.0
111 x = cos(0.)
112 do concurrent(i=1:2) &
113 !ERROR: 'bad1' may not appear in a locality-spec because it is not definable
114 !BECAUSE: 'bad1' is not a variable
115 local(bad1) &
116 !ERROR: 'bad2' may not appear in a locality-spec because it is not definable
117 !BECAUSE: 'bad2' is not a variable
118 local(bad2) &
119 !ERROR: 'bad3' may not appear in a locality-spec because it is not definable
120 !BECAUSE: 'bad3' is not a variable
121 local(bad3) &
122 !ERROR: 'cos' may not appear in a locality-spec because it is not definable
123 !BECAUSE: 'cos' is not a variable
124 local(cos)
125 end do
126 do concurrent(i=1:2) &
127 !ERROR: The name 'bad1' must be a variable to appear in a locality-spec
128 shared(bad1) &
129 !ERROR: The name 'bad2' must be a variable to appear in a locality-spec
130 shared(bad2) &
131 !ERROR: The name 'bad3' must be a variable to appear in a locality-spec
132 shared(bad3) &
133 !ERROR: The name 'cos' must be a variable to appear in a locality-spec
134 shared(cos)
135 end do
136 contains
137 subroutine bad3