Break circular dependency between FIR dialect and utilities
[llvm-project.git] / flang / test / Semantics / resolve57.f90
blobaa0ae45c8216f2ce81a403f691d8a6cebf021e2f
1 ! RUN: %python %S/test_errors.py %s %flang_fc1
2 ! Tests for the last sentence of C1128:
3 !A variable-name that is not permitted to appear in a variable definition
4 !context shall not appear in a LOCAL or LOCAL_INIT locality-spec.
6 subroutine s1(arg)
7 real, intent(in) :: arg
9 ! This is not OK because "arg" is "intent(in)"
10 !ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
11 do concurrent (i=1:5) local(arg)
12 end do
13 end subroutine s1
15 subroutine s2(arg)
16 real, value, intent(in) :: arg
18 ! This is not OK even though "arg" has the "value" attribute. C1128
19 ! explicitly excludes dummy arguments of INTENT(IN)
20 !ERROR: INTENT IN argument 'arg' not allowed in a locality-spec
21 do concurrent (i=1:5) local(arg)
22 end do
23 end subroutine s2
25 module m3
26 real, protected :: prot
27 real var
29 contains
30 subroutine sub()
31 ! C857 This is OK because of the "protected" attribute only applies to
32 ! accesses outside the module
33 do concurrent (i=1:5) local(prot)
34 end do
35 end subroutine sub
36 endmodule m3
38 subroutine s4()
39 use m3
41 ! C857 This is not OK because of the "protected" attribute
42 !ERROR: 'prot' may not appear in a locality-spec because it is not definable
43 !BECAUSE: 'prot' is protected in this scope
44 do concurrent (i=1:5) local(prot)
45 end do
47 ! C857 This is OK because of there's no "protected" attribute
48 do concurrent (i=1:5) local(var)
49 end do
50 end subroutine s4
52 subroutine s5()
53 real :: a, b, c, d, e
55 associate (a => b + c, d => e)
56 b = 3.0
57 ! C1101 This is OK because 'd' is associated with a variable
58 do concurrent (i=1:5) local(d)
59 end do
61 ! C1101 This is not OK because 'a' is not associated with a variable
62 !ERROR: 'a' may not appear in a locality-spec because it is not definable
63 !BECAUSE: 'a' is construct associated with an expression
64 do concurrent (i=1:5) local(a)
65 end do
66 end associate
67 end subroutine s5
69 subroutine s6()
70 type point
71 real :: x, y
72 end type point
74 type, extends(point) :: color_point
75 integer :: color
76 end type color_point
78 type(point), target :: c, d
79 class(point), pointer :: p_or_c
81 p_or_c => c
82 select type ( a => p_or_c )
83 type is ( point )
84 ! C1158 This is OK because 'a' is associated with a variable
85 do concurrent (i=1:5) local(a)
86 end do
87 end select
89 select type ( a => func() )
90 type is ( point )
91 ! C1158 This is OK because 'a' is associated with a variable
92 do concurrent (i=1:5) local(a)
93 end do
94 end select
96 select type ( a => (func()) )
97 type is ( point )
98 ! C1158 This is not OK because 'a' is not associated with a variable
99 !ERROR: 'a' may not appear in a locality-spec because it is not definable
100 !BECAUSE: 'a' is construct associated with an expression
101 do concurrent (i=1:5) local(a)
102 end do
103 end select
105 contains
106 function func()
107 class(point), pointer :: func
108 func => c
109 end function func
110 end subroutine s6
112 module m4
113 real, protected :: prot
114 real var
115 endmodule m4
117 pure subroutine s7()
118 use m4
120 ! C1594 This is not OK because we're in a PURE subroutine
121 !ERROR: 'var' may not appear in a locality-spec because it is not definable
122 !BECAUSE: 'var' may not be defined in pure subprogram 's7' because it is USE-associated
123 do concurrent (i=1:5) local(var)
124 end do
125 end subroutine s7
127 subroutine s8()
128 integer, parameter :: iconst = 343
130 !ERROR: 'iconst' may not appear in a locality-spec because it is not definable
131 !BECAUSE: 'iconst' is not a variable
132 do concurrent (i=1:5) local(iconst)
133 end do
134 end subroutine s8