• Home
  • Line#
  • Scopes#
  • Navigate#
  • Raw
  • Download
1!RUN: %S/test_errors.sh %s %t %f18
2subroutine s1
3  integer i, j
4  real r(2)
5  !ERROR: Equivalence set must have more than one object
6  equivalence(i, j),(r(1))
7end
8
9subroutine s2
10  integer i
11  type t
12    integer :: a
13    integer :: b(10)
14  end type
15  type(t) :: x
16  !ERROR: Derived type component 'x%a' is not allowed in an equivalence set
17  equivalence(x%a, i)
18  !ERROR: Derived type component 'x%b(2)' is not allowed in an equivalence set
19  equivalence(i, x%b(2))
20end
21
22integer function f3(x)
23  real x
24  !ERROR: Dummy argument 'x' is not allowed in an equivalence set
25  equivalence(i, x)
26  !ERROR: Function result 'f3' is not allow in an equivalence set
27  equivalence(f3, i)
28end
29
30subroutine s4
31  integer :: y
32  !ERROR: Pointer 'x' is not allowed in an equivalence set
33  !ERROR: Allocatable variable 'y' is not allowed in an equivalence set
34  equivalence(x, y)
35  real, pointer :: x
36  allocatable :: y
37end
38
39subroutine s5
40  integer, parameter :: k = 123
41  real :: x(10)
42  real, save :: y[1:*]
43  !ERROR: Coarray 'y' is not allowed in an equivalence set
44  equivalence(x, y)
45  !ERROR: Variable 'z' with BIND attribute is not allowed in an equivalence set
46  equivalence(x, z)
47  !ERROR: Variable 'z' with BIND attribute is not allowed in an equivalence set
48  equivalence(x(2), z(3))
49  real, bind(C) :: z(10)
50  !ERROR: Named constant 'k' is not allowed in an equivalence set
51  equivalence(x(2), k)
52  !ERROR: Variable 'w' in common block with BIND attribute is not allowed in an equivalence set
53  equivalence(x(10), w)
54  logical :: w(10)
55  bind(C, name="c") /c/
56  common /c/ w
57  integer, target :: u
58  !ERROR: Variable 'u' with TARGET attribute is not allowed in an equivalence set
59  equivalence(x(1), u)
60end
61
62subroutine s6
63  type t1
64    sequence
65    real, pointer :: p
66  end type
67  type :: t2
68    sequence
69    type(t1) :: b
70  end type
71  real :: x0
72  type(t1) :: x1
73  type(t2) :: x2
74  !ERROR: Derived type object 'x1' with pointer ultimate component is not allowed in an equivalence set
75  equivalence(x0, x1)
76  !ERROR: Derived type object 'x2' with pointer ultimate component is not allowed in an equivalence set
77  equivalence(x0, x2)
78end
79
80subroutine s7
81  type t1
82  end type
83  real :: x0
84  type(t1) :: x1
85  !ERROR: Nonsequence derived type object 'x1' is not allowed in an equivalence set
86  equivalence(x0, x1)
87end
88
89module m8
90  real :: x
91  real :: y(10)
92end
93subroutine s8
94  use m8
95  !ERROR: Use-associated variable 'x' is not allowed in an equivalence set
96  equivalence(x, z)
97  !ERROR: Use-associated variable 'y' is not allowed in an equivalence set
98  equivalence(y(1), z)
99end
100
101subroutine s9
102  character(10) :: c
103  real :: d(10)
104  integer, parameter :: n = 2
105  integer :: i, j
106  !ERROR: Substring with nonconstant bound 'n+j' is not allowed in an equivalence set
107  equivalence(c(n+1:n+j), i)
108  !ERROR: Substring with zero length is not allowed in an equivalence set
109  equivalence(c(n:1), i)
110  !ERROR: Array with nonconstant subscript 'j-1' is not allowed in an equivalence set
111  equivalence(d(j-1), i)
112  !ERROR: Array section 'd(1:n)' is not allowed in an equivalence set
113  equivalence(d(1:n), i)
114  character(4) :: a(10)
115  equivalence(c, a(10)(1:2))
116  !ERROR: 'a(10_8)(2_8:2_8)' and 'a(10_8)(1_8:1_8)' cannot have the same first storage unit
117  equivalence(c, a(10)(2:3))
118end
119
120subroutine s10
121  integer, parameter :: i(4) = [1, 2, 3, 4]
122  real :: x(10)
123  real :: y(4)
124  !ERROR: Array with vector subscript 'i' is not allowed in an equivalence set
125  equivalence(x(i), y)
126end
127
128subroutine s11(n)
129  integer :: n
130  real :: x(n), y
131  !ERROR: Automatic object 'x' is not allowed in an equivalence set
132  equivalence(x(1), y)
133end
134
135module s12
136  real, protected :: a
137  integer :: b
138  !ERROR: Equivalence set cannot contain 'a' with PROTECTED attribute and 'b' without
139  equivalence(a, b)
140  !ERROR: Equivalence set cannot contain 'a' with PROTECTED attribute and 'b' without
141  equivalence(b, a)
142end
143
144module s13
145  logical(8) :: a
146  character(4) :: b
147  type :: t1
148    sequence
149    complex :: z
150  end type
151  type :: t2
152    sequence
153    type(t1) :: w
154  end type
155  type(t2) :: c
156  !ERROR: Equivalence set cannot contain 'b' that is character sequence type and 'a' that is not
157  equivalence(a, b)
158  !ERROR: Equivalence set cannot contain 'c' that is numeric sequence type and 'a' that is not
159  equivalence(c, a)
160  double precision :: d
161  double complex :: e
162  !OK: d and e are considered to be a default kind numeric type
163  equivalence(c, d, e)
164end
165
166module s14
167  real :: a(10), b, c, d
168  !ERROR: 'a(2_8)' and 'a(1_8)' cannot have the same first storage unit
169  equivalence(a(1), a(2))
170  equivalence(b, a(3))
171  !ERROR: 'a(4_8)' and 'a(3_8)' cannot have the same first storage unit
172  equivalence(a(4), b)
173  equivalence(c, a(5))
174  !ERROR: 'a(6_8)' and 'a(5_8)' cannot have the same first storage unit
175  equivalence(a(6), d)
176  equivalence(c, d)
177end
178
179module s15
180  real :: a(2), b(2)
181  equivalence(a(2),b(1))
182  !ERROR: 'a(3_8)' and 'a(1_8)' cannot have the same first storage unit
183  equivalence(b(2),a(1))
184end module
185
186subroutine s16
187
188  integer var, dupName
189
190  ! There should be no error message for the following
191  equivalence (dupName, var)
192
193  interface
194    subroutine interfaceSub (dupName)
195      integer dupName
196    end subroutine interfaceSub
197  end interface
198
199end subroutine s16
200