[LoopReroll] Add an extra defensive check to avoid SCEV assertion.
[llvm-project.git] / flang / test / Semantics / resolve35.f90
blobbbefe2791a49ac8726b0225aea7ac5b8b633bdb6
1 ! RUN: %S/test_errors.sh %s %t %flang_fc1
2 ! REQUIRES: shell
3 ! Construct names
5 subroutine s1
6 real :: foo
7 !ERROR: 'foo' is already declared in this scoping unit
8 foo: block
9 end block foo
10 end
12 subroutine s2(x)
13 logical :: x
14 foo: if (x) then
15 end if foo
16 !ERROR: 'foo' is already declared in this scoping unit
17 foo: do i = 1, 10
18 end do foo
19 end
21 subroutine s3
22 real :: a(10,10), b(10,10)
23 type y; end type
24 integer(8) :: x
25 !ERROR: Index name 'y' conflicts with existing identifier
26 forall(x=1:10, y=1:10)
27 a(x, y) = b(x, y)
28 end forall
29 !ERROR: Index name 'y' conflicts with existing identifier
30 forall(x=1:10, y=1:10) a(x, y) = b(x, y)
31 end
33 subroutine s4
34 real :: a(10), b(10)
35 complex :: x
36 integer :: i(2)
37 !ERROR: Must have INTEGER type, but is COMPLEX(4)
38 forall(x=1:10)
39 !ERROR: Must have INTEGER type, but is COMPLEX(4)
40 !ERROR: Must have INTEGER type, but is COMPLEX(4)
41 a(x) = b(x)
42 end forall
43 !ERROR: Must have INTEGER type, but is REAL(4)
44 forall(y=1:10)
45 !ERROR: Must have INTEGER type, but is REAL(4)
46 !ERROR: Must have INTEGER type, but is REAL(4)
47 a(y) = b(y)
48 end forall
49 !ERROR: Index variable 'i' is not scalar
50 forall(i=1:10)
51 a(i) = b(i)
52 end forall
53 end
55 subroutine s6
56 integer, parameter :: n = 4
57 real, dimension(n) :: x
58 data(x(i), i=1, n) / n * 0.0 /
59 !ERROR: Index name 't' conflicts with existing identifier
60 forall(t=1:n) x(t) = 0.0
61 contains
62 subroutine t
63 end
64 end
66 subroutine s6b
67 integer, parameter :: k = 4
68 integer :: l = 4
69 forall(integer(k) :: i = 1:10)
70 end forall
71 ! C713 A scalar-int-constant-name shall be a named constant of type integer.
72 !ERROR: Must be a constant value
73 forall(integer(l) :: i = 1:10)
74 end forall
75 end
77 subroutine s7
78 !ERROR: 'i' is already declared in this scoping unit
79 do concurrent(integer::i=1:5) local(j, i) &
80 !ERROR: 'j' is already declared in this scoping unit
81 local_init(k, j) &
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 local(bad1) &
115 !ERROR: 'bad2' may not appear in a locality-spec because it is not definable
116 local(bad2) &
117 !ERROR: 'bad3' may not appear in a locality-spec because it is not definable
118 local(bad3) &
119 !ERROR: 'cos' may not appear in a locality-spec because it is not definable
120 local(cos)
121 end do
122 do concurrent(i=1:2) &
123 !ERROR: The name 'bad1' must be a variable to appear in a locality-spec
124 shared(bad1) &
125 !ERROR: The name 'bad2' must be a variable to appear in a locality-spec
126 shared(bad2) &
127 !ERROR: The name 'bad3' must be a variable to appear in a locality-spec
128 shared(bad3) &
129 !ERROR: The name 'cos' must be a variable to appear in a locality-spec
130 shared(cos)
131 end do
132 contains
133 subroutine bad3