xref: /llvm-project/flang/test/Semantics/resolve25.f90 (revision a3e9d3c2c7e9f8766bf03c63e43675258cc611ee)
1! RUN: %python %S/test_errors.py %s %flang_fc1
2module m
3  interface foo
4    real function s1(x)
5      real x
6    end
7    !ERROR: 's2' is not a module procedure
8    module procedure s2
9    !ERROR: 's3' is not a procedure
10    procedure s3
11    !ERROR: Procedure 's1' is already specified in generic 'foo'
12    procedure s1
13  end interface
14  interface
15    real function s4(x,y)
16      real, intent(in) :: x,y
17    end function
18    complex function s2(x,y)
19      complex, intent(in) :: x,y
20    end function
21  end interface
22  generic :: bar => s4
23  generic :: bar => s2
24  !ERROR: Procedure 's4' is already specified in generic 'bar'
25  generic :: bar => s4
26
27  generic :: operator(.foo.)=> s4
28  generic :: operator(.foo.)=> s2
29  !ERROR: Procedure 's4' is already specified in generic 'OPERATOR(.foo.)'
30  generic :: operator(.foo.)=> s4
31end module
32
33module m2
34  interface
35    integer function f(x, y)
36      logical, intent(in) :: x, y
37    end function
38  end interface
39  generic :: operator(+)=> f
40  !ERROR: Procedure 'f' is already specified in generic 'OPERATOR(+)'
41  generic :: operator(+)=> f
42end
43
44module m3
45  interface operator(.ge.)
46    procedure f
47  end interface
48  interface operator(>=)
49    !ERROR: Procedure 'f' is already specified in generic 'OPERATOR(.GE.)'
50    procedure f
51  end interface
52  generic :: operator(>) => f
53  !ERROR: Procedure 'f' is already specified in generic 'OPERATOR(>)'
54  generic :: operator(.gt.) => f
55contains
56  logical function f(x, y) result(result)
57    logical, intent(in) :: x, y
58    result = .true.
59  end
60end
61