1! RUN: %S/test_errors.sh %s %t %flang_fc1
2! REQUIRES: shell
3! Invalid operand types when user-defined operator is available
4module m1
5  type :: t
6  end type
7  interface operator(==)
8    logical function eq_tt(x, y)
9      import :: t
10      type(t), intent(in) :: x, y
11    end
12  end interface
13  interface operator(+)
14    logical function add_tr(x, y)
15      import :: t
16      type(t), intent(in) :: x
17      real, intent(in) :: y
18    end
19    logical function plus_t(x)
20      import :: t
21      type(t), intent(in) :: x
22    end
23    logical function add_12(x, y)
24      real, intent(in) :: x(:), y(:,:)
25    end
26  end interface
27  interface operator(.and.)
28    logical function and_tr(x, y)
29      import :: t
30      type(t), intent(in) :: x
31      real, intent(in) :: y
32    end
33  end interface
34  interface operator(//)
35    logical function concat_tt(x, y)
36      import :: t
37      type(t), intent(in) :: x, y
38    end
39  end interface
40  interface operator(.not.)
41    logical function not_r(x)
42      real, intent(in) :: x
43    end
44  end interface
45  type(t) :: x, y
46  real :: r
47  logical :: l
48  integer :: iVar
49  complex :: cvar
50  character :: charVar
51contains
52  subroutine test_relational()
53    l = x == y  !OK
54    l = x .eq. y  !OK
55    l = x .eq. y  !OK
56    l = iVar == z'fe' !OK
57    l = z'fe' == iVar !OK
58    l = r == z'fe' !OK
59    l = z'fe' == r !OK
60    l = cVar == z'fe' !OK
61    l = z'fe' == cVar !OK
62    !ERROR: No intrinsic or user-defined OPERATOR(==) matches operand types CHARACTER(KIND=1) and INTEGER(4)
63    l = charVar == z'fe'
64    !ERROR: No intrinsic or user-defined OPERATOR(==) matches operand types INTEGER(4) and CHARACTER(KIND=1)
65    l = z'fe' == charVar
66    !ERROR: No intrinsic or user-defined OPERATOR(==) matches operand types LOGICAL(4) and INTEGER(4)
67    l = l == z'fe' !OK
68    !ERROR: No intrinsic or user-defined OPERATOR(==) matches operand types INTEGER(4) and LOGICAL(4)
69    l = z'fe' == l !OK
70    !ERROR: No intrinsic or user-defined OPERATOR(==) matches operand types TYPE(t) and REAL(4)
71    l = x == r
72
73    lVar = z'a' == b'1010' !OK
74  end
75  subroutine test_numeric()
76    l = x + r  !OK
77    !ERROR: No intrinsic or user-defined OPERATOR(+) matches operand types REAL(4) and TYPE(t)
78    l = r + x
79  end
80  subroutine test_logical()
81    l = x .and. r  !OK
82    !ERROR: No intrinsic or user-defined OPERATOR(.AND.) matches operand types REAL(4) and TYPE(t)
83    l = r .and. x
84  end
85  subroutine test_unary()
86    l = +x  !OK
87    !ERROR: No intrinsic or user-defined OPERATOR(+) matches operand type LOGICAL(4)
88    l = +l
89    l = .not. r  !OK
90    !ERROR: No intrinsic or user-defined OPERATOR(.NOT.) matches operand type TYPE(t)
91    l = .not. x
92  end
93  subroutine test_concat()
94    l = x // y  !OK
95    !ERROR: No intrinsic or user-defined OPERATOR(//) matches operand types TYPE(t) and REAL(4)
96    l = x // r
97  end
98  subroutine test_conformability(x, y)
99    real :: x(10), y(10,10)
100    l = x + y  !OK
101    !ERROR: No intrinsic or user-defined OPERATOR(+) matches rank 2 array of REAL(4) and rank 1 array of REAL(4)
102    l = y + x
103  end
104end
105
106! Invalid operand types when user-defined operator is not available
107module m2
108  intrinsic :: sin
109  type :: t
110  end type
111  type(t) :: x, y
112  real :: r
113  logical :: l
114contains
115  subroutine test_relational()
116    !ERROR: Operands of .EQ. must have comparable types; have TYPE(t) and REAL(4)
117    l = x == r
118    !ERROR: Subroutine name is not allowed here
119    l = r == test_numeric
120    !ERROR: Function call must have argument list
121    l = r == sin
122  end
123  subroutine test_numeric()
124    !ERROR: Operands of + must be numeric; have REAL(4) and TYPE(t)
125    l = r + x
126  end
127  subroutine test_logical()
128    !ERROR: Operands of .AND. must be LOGICAL; have REAL(4) and TYPE(t)
129    l = r .and. x
130  end
131  subroutine test_unary()
132    !ERROR: Operand of unary + must be numeric; have LOGICAL(4)
133    l = +l
134    !ERROR: Operand of .NOT. must be LOGICAL; have TYPE(t)
135    l = .not. x
136  end
137  subroutine test_concat(a, b)
138    character(4,kind=1) :: a
139    character(4,kind=2) :: b
140    character(4) :: c
141    !ERROR: Operands of // must be CHARACTER with the same kind; have CHARACTER(KIND=1) and CHARACTER(KIND=2)
142    c = a // b
143    !ERROR: Operands of // must be CHARACTER with the same kind; have TYPE(t) and REAL(4)
144    l = x // r
145  end
146  subroutine test_conformability(x, y)
147    real :: x(10), y(10,10)
148    !ERROR: Operands of + are not conformable; have rank 2 and rank 1
149    l = y + x
150  end
151end
152
153! Invalid untyped operands: user-defined operator doesn't affect errors
154module m3
155  interface operator(+)
156    logical function add(x, y)
157      logical, intent(in) :: x
158      integer, value :: y
159    end
160  end interface
161contains
162  subroutine s1(x, y)
163    logical :: x
164    integer :: y
165    integer, pointer :: px
166    logical :: l
167    complex :: z
168    y = y + z'1'  !OK
169    !ERROR: Operands of + must be numeric; have untyped and COMPLEX(4)
170    z = z'1' + z
171    y = +z'1'  !OK
172    !ERROR: Operand of unary - must be numeric; have untyped
173    y = -z'1'
174    !ERROR: Operands of + must be numeric; have LOGICAL(4) and untyped
175    y = x + z'1'
176    !ERROR: NULL() not allowed as an operand of a relational operator
177    l = x /= null()
178    !ERROR: NULL() not allowed as an operand of a relational operator
179    l = null(px) /= null(px)
180    !ERROR: NULL() not allowed as an operand of a relational operator
181    l = x /= null(px)
182    !ERROR: NULL() not allowed as an operand of a relational operator
183    l = px /= null()
184    !ERROR: NULL() not allowed as an operand of a relational operator
185    l = px /= null(px)
186    !ERROR: NULL() not allowed as an operand of a relational operator
187    l = null() /= null()
188  end
189end
190
191! Test alternate operators. They aren't enabled by default so should be
192! treated as defined operators, not intrinsic ones.
193module m4
194contains
195  subroutine s1(x, y, z)
196    logical :: x
197    real :: y, z
198    !ERROR: No operator .A. defined for REAL(4) and REAL(4)
199    x = y .a. z
200    !ERROR: No operator .O. defined for REAL(4) and REAL(4)
201    x = y .o. z
202    !ERROR: No operator .N. defined for REAL(4)
203    x = .n. y
204    !ERROR: No operator .XOR. defined for REAL(4) and REAL(4)
205    x = y .xor. z
206    !ERROR: No operator .X. defined for REAL(4)
207    x = .x. y
208  end
209end
210
211! Like m4 in resolve63 but compiled with different options.
212! .A. is a defined operator.
213module m5
214  interface operator(.A.)
215    logical function f1(x, y)
216      integer, intent(in) :: x, y
217    end
218  end interface
219  interface operator(.and.)
220    logical function f2(x, y)
221      real, intent(in) :: x, y
222    end
223  end interface
224contains
225  subroutine s1(x, y, z)
226    logical :: x
227    complex :: y, z
228    !ERROR: No intrinsic or user-defined OPERATOR(.AND.) matches operand types COMPLEX(4) and COMPLEX(4)
229    x = y .and. z
230    !ERROR: No intrinsic or user-defined .A. matches operand types COMPLEX(4) and COMPLEX(4)
231    x = y .a. z
232  end
233end
234
235! Type-bound operators
236module m6
237  type :: t1
238  contains
239    procedure, pass(x) :: p1 => f1
240    generic :: operator(+) => p1
241  end type
242  type, extends(t1) :: t2
243  contains
244    procedure, pass(y) :: p2 => f2
245    generic :: operator(+) => p2
246  end type
247  type :: t3
248  contains
249    procedure, nopass :: p1 => f1
250    !ERROR: OPERATOR(+) procedure 'p1' may not have NOPASS attribute
251    generic :: operator(+) => p1
252  end type
253contains
254  integer function f1(x, y)
255    class(t1), intent(in) :: x
256    integer, intent(in) :: y
257  end
258  integer function f2(x, y)
259    class(t1), intent(in) :: x
260    class(t2), intent(in) :: y
261  end
262  subroutine test(x, y, z)
263    class(t1) :: x
264    class(t2) :: y
265    integer :: i
266    i = x + y
267    i = x + i
268    i = y + i
269    !ERROR: No intrinsic or user-defined OPERATOR(+) matches operand types TYPE(t2) and TYPE(t1)
270    i = y + x
271    !ERROR: No intrinsic or user-defined OPERATOR(+) matches operand types INTEGER(4) and TYPE(t1)
272    i = i + x
273  end
274end
275