xref: /llvm-project/flang/test/Semantics/resolve35.f90 (revision 90828d67ea35c86b76fc8f3dec5da03f645eadaf)
1! RUN: %python %S/test_errors.py %s %flang_fc1 -pedantic
2! Construct names
3
4subroutine s1
5  real :: foo
6  !ERROR: 'foo' is already declared in this scoping unit
7  foo: block
8  end block foo
9end
10
11subroutine 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
18end
19
20subroutine s3
21  real :: a(10,10), b(10,10)
22  type y; end type
23  integer(8) :: x
24  !PORTABILITY: Index variable 'y' should be a scalar object or common block if it is present in the enclosing scope
25  !ERROR: Must have INTEGER type, but is REAL(4)
26  forall(x=1:10, y=1:10)
27    !ERROR: Must have INTEGER type, but is REAL(4)
28    !ERROR: Must have INTEGER type, but is REAL(4)
29    a(x, y) = b(x, y)
30  end forall
31  !PORTABILITY: Index variable 'y' should be a scalar object or common block if it is present in the enclosing scope
32  !ERROR: Must have INTEGER type, but is REAL(4)
33  !ERROR: Must have INTEGER type, but is REAL(4)
34  !ERROR: Must have INTEGER type, but is REAL(4)
35  forall(x=1:10, y=1:10) a(x, y) = b(x, y)
36end
37
38subroutine s4
39  real :: a(10), b(10)
40  complex :: x
41  integer :: i(2)
42  !ERROR: Must have INTEGER type, but is COMPLEX(4)
43  forall(x=1:10)
44    !ERROR: Must have INTEGER type, but is COMPLEX(4)
45    !ERROR: Must have INTEGER type, but is COMPLEX(4)
46    a(x) = b(x)
47  end forall
48  !ERROR: Must have INTEGER type, but is REAL(4)
49  forall(y=1:10)
50    !ERROR: Must have INTEGER type, but is REAL(4)
51    !ERROR: Must have INTEGER type, but is REAL(4)
52    a(y) = b(y)
53  end forall
54  !PORTABILITY: Index variable 'i' should be scalar in the enclosing scope
55  forall(i=1:10)
56    a(i) = b(i)
57  end forall
58end
59
60subroutine s6
61  integer, parameter :: n = 4
62  real, dimension(n) :: x
63  data(x(i), i=1, n) / n * 0.0 /
64  !PORTABILITY: Index variable 't' should be a scalar object or common block if it is present in the enclosing scope
65  !ERROR: Must have INTEGER type, but is REAL(4)
66  !ERROR: Must have INTEGER type, but is REAL(4)
67  forall(t=1:n) x(t) = 0.0
68contains
69  subroutine t
70  end
71end
72
73subroutine s6b
74  integer, parameter :: k = 4
75  integer :: l = 4
76  forall(integer(k) :: i = 1:10)
77  end forall
78  ! C713 A scalar-int-constant-name shall be a named constant of type integer.
79  !ERROR: Must be a constant value
80  forall(integer(l) :: i = 1:10)
81  end forall
82end
83
84subroutine s7
85  !ERROR: 'i' is already declared in this scoping unit
86  do concurrent(integer::i=1:5) local(j, i) &
87      !ERROR: 'j' is already declared in this scoping unit
88      local_init(k, j) &
89      !WARNING: Variable 'a' with SHARED locality implicitly declared
90      shared(a)
91    a = j + 1
92  end do
93end
94
95subroutine s8
96  implicit none
97  !ERROR: No explicit type declared for 'i'
98  do concurrent(i=1:5) &
99    !ERROR: No explicit type declared for 'j'
100    local(j) &
101    !ERROR: No explicit type declared for 'k'
102    local_init(k)
103  end do
104end
105
106subroutine s9
107  integer :: j
108  !ERROR: 'i' is already declared in this scoping unit
109  do concurrent(integer::i=1:5) shared(i) &
110      shared(j) &
111      !ERROR: 'j' is already declared in this scoping unit
112      shared(j)
113  end do
114end
115
116subroutine s10
117  external bad1
118  real, parameter :: bad2 = 1.0
119  x = cos(0.)
120  do concurrent(i=1:2) &
121    !ERROR: 'bad1' may not appear in a locality-spec because it is not definable
122    !BECAUSE: 'bad1' is not a variable
123    local(bad1) &
124    !ERROR: 'bad2' may not appear in a locality-spec because it is not definable
125    !BECAUSE: 'bad2' is not a variable
126    local(bad2) &
127    !ERROR: 'bad3' may not appear in a locality-spec because it is not definable
128    !BECAUSE: 'bad3' is not a variable
129    local(bad3) &
130    !ERROR: 'cos' may not appear in a locality-spec because it is not definable
131    !BECAUSE: 'cos' is not a variable
132    local(cos)
133  end do
134  do concurrent(i=1:2) &
135    !ERROR: The name 'bad1' must be a variable to appear in a locality-spec
136    shared(bad1) &
137    !ERROR: The name 'bad2' must be a variable to appear in a locality-spec
138    shared(bad2) &
139    !ERROR: The name 'bad3' must be a variable to appear in a locality-spec
140    shared(bad3) &
141    !ERROR: The name 'cos' must be a variable to appear in a locality-spec
142    shared(cos)
143  end do
144contains
145  subroutine bad3
146  end
147end
148