1! RUN: %S/test_errors.sh %s %t %f18
2! Resolve generic based on number of arguments
3subroutine s1
4  interface f
5    real function f1(x)
6      optional :: x
7    end
8    real function f2(x, y)
9    end
10  end interface
11  z = f(1.0)
12  z = f(1.0, 2.0)
13  !ERROR: No specific procedure of generic 'f' matches the actual arguments
14  z = f(1.0, 2.0, 3.0)
15end
16
17! Elemental and non-element function both match: non-elemental one should be used
18subroutine s2
19  interface f
20    logical elemental function f1(x)
21      intent(in) :: x
22    end
23    real function f2(x)
24      real :: x(10)
25    end
26  end interface
27  real :: x, y(10), z
28  logical :: a
29  a = f(1.0)
30  !ERROR: No intrinsic or user-defined ASSIGNMENT(=) matches operand types LOGICAL(4) and REAL(4)
31  a = f(y)
32end
33
34! Resolve named operator
35subroutine s3
36  interface operator(.foo.)
37    pure integer(8) function f_real(x, y)
38      real, intent(in) :: x, y
39    end
40    pure integer(8) function f_integer(x, y)
41      integer, intent(in) :: x, y
42    end
43  end interface
44  logical :: a, b, c
45  x = y .foo. z  ! OK: f_real
46  i = j .foo. k  ! OK: f_integer
47  !ERROR: No intrinsic or user-defined .FOO. matches operand types LOGICAL(4) and LOGICAL(4)
48  a = b .foo. c
49end
50
51! Generic resolves successfully but error analyzing call
52module m4
53  real, protected :: x
54  real :: y
55  interface s
56    pure subroutine s1(x)
57      real, intent(out) :: x
58    end
59    subroutine s2(x, y)
60      real :: x, y
61    end
62  end interface
63end
64subroutine s4a
65  use m4
66  real :: z
67  !OK
68  call s(z)
69end
70subroutine s4b
71  use m4
72  !ERROR: Actual argument associated with INTENT(OUT) dummy argument 'x=' must be definable
73  call s(x)
74end
75pure subroutine s4c
76  use m4
77  !ERROR: Actual argument associated with INTENT(OUT) dummy argument 'x=' must be definable
78  call s(y)
79end
80