xref: /llvm-project/flang/test/Semantics/modfile07.f90 (revision a3e9d3c2c7e9f8766bf03c63e43675258cc611ee)
1dc453dcfSIvan Zhechev! RUN: %python %S/test_modfile.py %s %flang_fc1
264ab3302SCarolineConcatto! Check modfile generation for generic interfaces
364ab3302SCarolineConcattomodule m1
464ab3302SCarolineConcatto  interface foo
564ab3302SCarolineConcatto    real function s1(x,y)
664ab3302SCarolineConcatto      real, intent(in) :: x
764ab3302SCarolineConcatto      logical, intent(in) :: y
864ab3302SCarolineConcatto    end function
964ab3302SCarolineConcatto    complex function s2(x,y)
1064ab3302SCarolineConcatto      complex, intent(in) :: x
1164ab3302SCarolineConcatto      logical, intent(in) :: y
1264ab3302SCarolineConcatto    end function
1364ab3302SCarolineConcatto  end interface
1464ab3302SCarolineConcatto  generic :: operator ( + ) => s1, s2
1564ab3302SCarolineConcatto  interface operator ( /= )
1664ab3302SCarolineConcatto    logical function f1(x, y)
1764ab3302SCarolineConcatto      real, intent(in) :: x
1864ab3302SCarolineConcatto      logical, intent(in) :: y
1964ab3302SCarolineConcatto    end function
2064ab3302SCarolineConcatto  end interface
2164ab3302SCarolineConcatto  interface
2264ab3302SCarolineConcatto    logical function f2(x, y)
2364ab3302SCarolineConcatto      complex, intent(in) :: x
2464ab3302SCarolineConcatto      logical, intent(in) :: y
2564ab3302SCarolineConcatto    end function
2664ab3302SCarolineConcatto    logical function f3(x, y)
2764ab3302SCarolineConcatto      integer, intent(in) :: x
2864ab3302SCarolineConcatto      logical, intent(in) :: y
2964ab3302SCarolineConcatto    end function
3064ab3302SCarolineConcatto  end interface
3164ab3302SCarolineConcatto  generic :: operator(.ne.) => f2
3264ab3302SCarolineConcatto  generic :: operator(<>) => f3
3364ab3302SCarolineConcatto  private :: operator( .ne. )
3464ab3302SCarolineConcatto  interface bar
3564ab3302SCarolineConcatto    procedure :: s1
3664ab3302SCarolineConcatto    procedure :: s2
3764ab3302SCarolineConcatto    procedure :: s3
3864ab3302SCarolineConcatto    procedure :: s4
3964ab3302SCarolineConcatto  end interface
4064ab3302SCarolineConcatto  interface operator( .bar.)
4164ab3302SCarolineConcatto    procedure :: s1
4264ab3302SCarolineConcatto    procedure :: s2
4364ab3302SCarolineConcatto    procedure :: s3
4464ab3302SCarolineConcatto    procedure :: s4
4564ab3302SCarolineConcatto  end interface
4664ab3302SCarolineConcattocontains
4764ab3302SCarolineConcatto  logical function s3(x,y)
4864ab3302SCarolineConcatto    logical, intent(in) :: x,y
4964ab3302SCarolineConcatto  end function
5064ab3302SCarolineConcatto  integer function s4(x,y)
5164ab3302SCarolineConcatto    integer, intent(in) :: x,y
5264ab3302SCarolineConcatto  end function
5364ab3302SCarolineConcattoend
5464ab3302SCarolineConcatto!Expect: m1.mod
5564ab3302SCarolineConcatto!module m1
5664ab3302SCarolineConcatto! interface
5764ab3302SCarolineConcatto!  function s1(x,y)
5864ab3302SCarolineConcatto!   real(4),intent(in)::x
5964ab3302SCarolineConcatto!   logical(4),intent(in)::y
6064ab3302SCarolineConcatto!   real(4)::s1
6164ab3302SCarolineConcatto!  end
6264ab3302SCarolineConcatto! end interface
6364ab3302SCarolineConcatto! interface
6464ab3302SCarolineConcatto!  function s2(x,y)
6564ab3302SCarolineConcatto!   complex(4),intent(in)::x
6664ab3302SCarolineConcatto!   logical(4),intent(in)::y
6764ab3302SCarolineConcatto!   complex(4)::s2
6864ab3302SCarolineConcatto!  end
6964ab3302SCarolineConcatto! end interface
7064ab3302SCarolineConcatto! interface
7164ab3302SCarolineConcatto!  function f1(x,y)
7264ab3302SCarolineConcatto!   real(4),intent(in)::x
7364ab3302SCarolineConcatto!   logical(4),intent(in)::y
7464ab3302SCarolineConcatto!   logical(4)::f1
7564ab3302SCarolineConcatto!  end
7664ab3302SCarolineConcatto! end interface
7764ab3302SCarolineConcatto! interface
7864ab3302SCarolineConcatto!  function f2(x,y)
7964ab3302SCarolineConcatto!   complex(4),intent(in)::x
8064ab3302SCarolineConcatto!   logical(4),intent(in)::y
8164ab3302SCarolineConcatto!   logical(4)::f2
8264ab3302SCarolineConcatto!  end
8364ab3302SCarolineConcatto! end interface
8464ab3302SCarolineConcatto! interface
8564ab3302SCarolineConcatto!  function f3(x,y)
8664ab3302SCarolineConcatto!   integer(4),intent(in)::x
8764ab3302SCarolineConcatto!   logical(4),intent(in)::y
8864ab3302SCarolineConcatto!   logical(4)::f3
8964ab3302SCarolineConcatto!  end
9064ab3302SCarolineConcatto! end interface
91*a3e9d3c2SPeter Klausler! interface foo
92*a3e9d3c2SPeter Klausler!  procedure::s1
93*a3e9d3c2SPeter Klausler!  procedure::s2
94*a3e9d3c2SPeter Klausler! end interface
95*a3e9d3c2SPeter Klausler! interface operator(+)
96*a3e9d3c2SPeter Klausler!  procedure::s1
97*a3e9d3c2SPeter Klausler!  procedure::s2
98*a3e9d3c2SPeter Klausler! end interface
99*a3e9d3c2SPeter Klausler! interface operator(/=)
100*a3e9d3c2SPeter Klausler!  procedure::f1
101*a3e9d3c2SPeter Klausler!  procedure::f2
102*a3e9d3c2SPeter Klausler!  procedure::f3
103*a3e9d3c2SPeter Klausler! end interface
104*a3e9d3c2SPeter Klausler! private::operator(/=)
10564ab3302SCarolineConcatto! interface bar
10664ab3302SCarolineConcatto!  procedure::s1
10764ab3302SCarolineConcatto!  procedure::s2
10864ab3302SCarolineConcatto!  procedure::s3
10964ab3302SCarolineConcatto!  procedure::s4
11064ab3302SCarolineConcatto! end interface
11164ab3302SCarolineConcatto! interface operator(.bar.)
11264ab3302SCarolineConcatto!  procedure::s1
11364ab3302SCarolineConcatto!  procedure::s2
11464ab3302SCarolineConcatto!  procedure::s3
11564ab3302SCarolineConcatto!  procedure::s4
11664ab3302SCarolineConcatto! end interface
11764ab3302SCarolineConcatto!contains
11864ab3302SCarolineConcatto! function s3(x,y)
11964ab3302SCarolineConcatto!  logical(4),intent(in)::x
12064ab3302SCarolineConcatto!  logical(4),intent(in)::y
12164ab3302SCarolineConcatto!  logical(4)::s3
12264ab3302SCarolineConcatto! end
12364ab3302SCarolineConcatto! function s4(x,y)
12464ab3302SCarolineConcatto!  integer(4),intent(in)::x
12564ab3302SCarolineConcatto!  integer(4),intent(in)::y
12664ab3302SCarolineConcatto!  integer(4)::s4
12764ab3302SCarolineConcatto! end
12864ab3302SCarolineConcatto!end
12964ab3302SCarolineConcatto
13064ab3302SCarolineConcattomodule m1b
13164ab3302SCarolineConcatto  use m1
13264ab3302SCarolineConcattoend
13364ab3302SCarolineConcatto!Expect: m1b.mod
13464ab3302SCarolineConcatto!module m1b
13564ab3302SCarolineConcatto! use m1,only:foo
13664ab3302SCarolineConcatto! use m1,only:s1
13764ab3302SCarolineConcatto! use m1,only:s2
13864ab3302SCarolineConcatto! use m1,only:operator(+)
13964ab3302SCarolineConcatto! use m1,only:f1
14064ab3302SCarolineConcatto! use m1,only:f2
14164ab3302SCarolineConcatto! use m1,only:f3
14264ab3302SCarolineConcatto! use m1,only:bar
14364ab3302SCarolineConcatto! use m1,only:operator(.bar.)
14464ab3302SCarolineConcatto! use m1,only:s3
14564ab3302SCarolineConcatto! use m1,only:s4
14664ab3302SCarolineConcatto!end
14764ab3302SCarolineConcatto
14864ab3302SCarolineConcattomodule m1c
14964ab3302SCarolineConcatto  use m1, only: myfoo => foo
15064ab3302SCarolineConcatto  use m1, only: operator(.bar.)
15164ab3302SCarolineConcatto  use m1, only: operator(.mybar.) => operator(.bar.)
15264ab3302SCarolineConcatto  use m1, only: operator(+)
15364ab3302SCarolineConcattoend
15464ab3302SCarolineConcatto!Expect: m1c.mod
15564ab3302SCarolineConcatto!module m1c
15664ab3302SCarolineConcatto! use m1,only:myfoo=>foo
15764ab3302SCarolineConcatto! use m1,only:operator(.bar.)
15864ab3302SCarolineConcatto! use m1,only:operator(.mybar.)=>operator(.bar.)
15964ab3302SCarolineConcatto! use m1,only:operator(+)
16064ab3302SCarolineConcatto!end
16164ab3302SCarolineConcatto
16264ab3302SCarolineConcattomodule m2
16364ab3302SCarolineConcatto  interface foo
16464ab3302SCarolineConcatto    procedure foo
16564ab3302SCarolineConcatto  end interface
16664ab3302SCarolineConcattocontains
16764ab3302SCarolineConcatto  complex function foo()
16864ab3302SCarolineConcatto    foo = 1.0
16964ab3302SCarolineConcatto  end
17064ab3302SCarolineConcattoend
17164ab3302SCarolineConcatto!Expect: m2.mod
17264ab3302SCarolineConcatto!module m2
17364ab3302SCarolineConcatto! interface foo
17464ab3302SCarolineConcatto!  procedure::foo
17564ab3302SCarolineConcatto! end interface
17664ab3302SCarolineConcatto!contains
17764ab3302SCarolineConcatto! function foo()
17864ab3302SCarolineConcatto!  complex(4)::foo
17964ab3302SCarolineConcatto! end
18064ab3302SCarolineConcatto!end
18164ab3302SCarolineConcatto
18264ab3302SCarolineConcattomodule m2b
18364ab3302SCarolineConcatto  type :: foo
18464ab3302SCarolineConcatto    real :: x
18564ab3302SCarolineConcatto  end type
18664ab3302SCarolineConcatto  interface foo
18764ab3302SCarolineConcatto  end interface
18864ab3302SCarolineConcatto  private :: bar
18964ab3302SCarolineConcatto  interface bar
19064ab3302SCarolineConcatto  end interface
19164ab3302SCarolineConcattoend
19264ab3302SCarolineConcatto!Expect: m2b.mod
19364ab3302SCarolineConcatto!module m2b
19464ab3302SCarolineConcatto! type::foo
19564ab3302SCarolineConcatto!  real(4)::x
19664ab3302SCarolineConcatto! end type
197*a3e9d3c2SPeter Klausler! interface foo
198*a3e9d3c2SPeter Klausler! end interface
19964ab3302SCarolineConcatto! interface bar
20064ab3302SCarolineConcatto! end interface
20164ab3302SCarolineConcatto! private::bar
20264ab3302SCarolineConcatto!end
20364ab3302SCarolineConcatto
20464ab3302SCarolineConcatto! Test interface nested inside another interface
20564ab3302SCarolineConcattomodule m3
20664ab3302SCarolineConcatto  interface g
20764ab3302SCarolineConcatto    subroutine s1(f)
20864ab3302SCarolineConcatto      interface
20964ab3302SCarolineConcatto        real function f(x)
21064ab3302SCarolineConcatto          interface
21164ab3302SCarolineConcatto            subroutine x()
21264ab3302SCarolineConcatto            end subroutine
21364ab3302SCarolineConcatto          end interface
21464ab3302SCarolineConcatto        end function
21564ab3302SCarolineConcatto      end interface
21664ab3302SCarolineConcatto    end subroutine
21764ab3302SCarolineConcatto  end interface
21864ab3302SCarolineConcattoend
21964ab3302SCarolineConcatto!Expect: m3.mod
22064ab3302SCarolineConcatto!module m3
22164ab3302SCarolineConcatto! interface
22264ab3302SCarolineConcatto!  subroutine s1(f)
22364ab3302SCarolineConcatto!   interface
22464ab3302SCarolineConcatto!    function f(x)
22564ab3302SCarolineConcatto!     interface
22664ab3302SCarolineConcatto!      subroutine x()
22764ab3302SCarolineConcatto!      end
22864ab3302SCarolineConcatto!     end interface
22964ab3302SCarolineConcatto!     real(4)::f
23064ab3302SCarolineConcatto!    end
23164ab3302SCarolineConcatto!   end interface
23264ab3302SCarolineConcatto!  end
23364ab3302SCarolineConcatto! end interface
234*a3e9d3c2SPeter Klausler! interface g
235*a3e9d3c2SPeter Klausler!  procedure::s1
236*a3e9d3c2SPeter Klausler! end interface
23764ab3302SCarolineConcatto!end
23864ab3302SCarolineConcatto
23964ab3302SCarolineConcattomodule m4
24064ab3302SCarolineConcatto  interface foo
24164ab3302SCarolineConcatto    integer function foo()
24264ab3302SCarolineConcatto    end function
24364ab3302SCarolineConcatto    integer function f(x)
24464ab3302SCarolineConcatto    end function
24564ab3302SCarolineConcatto  end interface
24664ab3302SCarolineConcattoend
24764ab3302SCarolineConcattosubroutine s4
24864ab3302SCarolineConcatto  use m4
24964ab3302SCarolineConcatto  i = foo()
25064ab3302SCarolineConcattoend
25164ab3302SCarolineConcatto!Expect: m4.mod
25264ab3302SCarolineConcatto!module m4
25364ab3302SCarolineConcatto! interface
25464ab3302SCarolineConcatto!  function foo()
25564ab3302SCarolineConcatto!   integer(4)::foo
25664ab3302SCarolineConcatto!  end
25764ab3302SCarolineConcatto! end interface
25864ab3302SCarolineConcatto! interface
25964ab3302SCarolineConcatto!  function f(x)
26064ab3302SCarolineConcatto!   real(4)::x
26164ab3302SCarolineConcatto!   integer(4)::f
26264ab3302SCarolineConcatto!  end
26364ab3302SCarolineConcatto! end interface
264*a3e9d3c2SPeter Klausler! interface foo
265*a3e9d3c2SPeter Klausler!  procedure::foo
266*a3e9d3c2SPeter Klausler!  procedure::f
267*a3e9d3c2SPeter Klausler! end interface
26864ab3302SCarolineConcatto!end
26964ab3302SCarolineConcatto
27064ab3302SCarolineConcatto! Compile contents of m4.mod and verify it gets the same thing again.
27164ab3302SCarolineConcattomodule m5
27264ab3302SCarolineConcatto interface foo
27364ab3302SCarolineConcatto  procedure::foo
27464ab3302SCarolineConcatto  procedure::f
27564ab3302SCarolineConcatto end interface
27664ab3302SCarolineConcatto interface
27764ab3302SCarolineConcatto  function foo()
27864ab3302SCarolineConcatto   integer(4)::foo
27964ab3302SCarolineConcatto  end
28064ab3302SCarolineConcatto end interface
28164ab3302SCarolineConcatto interface
28264ab3302SCarolineConcatto  function f(x)
28364ab3302SCarolineConcatto   integer(4)::f
28464ab3302SCarolineConcatto   real(4)::x
28564ab3302SCarolineConcatto  end
28664ab3302SCarolineConcatto end interface
28764ab3302SCarolineConcattoend
28864ab3302SCarolineConcatto!Expect: m5.mod
28964ab3302SCarolineConcatto!module m5
29064ab3302SCarolineConcatto! interface
29164ab3302SCarolineConcatto!  function foo()
29264ab3302SCarolineConcatto!   integer(4)::foo
29364ab3302SCarolineConcatto!  end
29464ab3302SCarolineConcatto! end interface
29564ab3302SCarolineConcatto! interface
29664ab3302SCarolineConcatto!  function f(x)
29764ab3302SCarolineConcatto!   real(4)::x
29864ab3302SCarolineConcatto!   integer(4)::f
29964ab3302SCarolineConcatto!  end
30064ab3302SCarolineConcatto! end interface
301*a3e9d3c2SPeter Klausler! interface foo
302*a3e9d3c2SPeter Klausler!  procedure::foo
303*a3e9d3c2SPeter Klausler!  procedure::f
304*a3e9d3c2SPeter Klausler! end interface
30564ab3302SCarolineConcatto!end
30664ab3302SCarolineConcatto
30764ab3302SCarolineConcattomodule m6a
30864ab3302SCarolineConcatto  interface operator(<)
30964ab3302SCarolineConcatto    logical function lt(x, y)
31064ab3302SCarolineConcatto      logical, intent(in) :: x, y
31164ab3302SCarolineConcatto    end function
31264ab3302SCarolineConcatto  end interface
31364ab3302SCarolineConcattoend
31464ab3302SCarolineConcatto!Expect: m6a.mod
31564ab3302SCarolineConcatto!module m6a
31664ab3302SCarolineConcatto! interface
31764ab3302SCarolineConcatto!  function lt(x,y)
31864ab3302SCarolineConcatto!   logical(4),intent(in)::x
31964ab3302SCarolineConcatto!   logical(4),intent(in)::y
32064ab3302SCarolineConcatto!   logical(4)::lt
32164ab3302SCarolineConcatto!  end
32264ab3302SCarolineConcatto! end interface
323*a3e9d3c2SPeter Klausler! interface operator(<)
324*a3e9d3c2SPeter Klausler!  procedure::lt
325*a3e9d3c2SPeter Klausler! end interface
32664ab3302SCarolineConcatto!end
32764ab3302SCarolineConcatto
32864ab3302SCarolineConcattomodule m6b
32964ab3302SCarolineConcatto  use m6a, only: operator(.lt.)
33064ab3302SCarolineConcattoend
33164ab3302SCarolineConcatto!Expect: m6b.mod
33264ab3302SCarolineConcatto!module m6b
33364ab3302SCarolineConcatto! use m6a,only:operator(.lt.)
33464ab3302SCarolineConcatto!end
33586f59de1STim Keith
33686f59de1STim Keithmodule m7a
33786f59de1STim Keith  interface g_integer
33886f59de1STim Keith    module procedure s
33986f59de1STim Keith  end interface
34086f59de1STim Keith  private :: s
34186f59de1STim Keithcontains
34286f59de1STim Keith  subroutine s(x)
34386f59de1STim Keith    integer :: x
34486f59de1STim Keith  end
34586f59de1STim Keithend
34686f59de1STim Keith!Expect: m7a.mod
34786f59de1STim Keith!module m7a
348*a3e9d3c2SPeter Klausler! private :: s
34986f59de1STim Keith! interface g_integer
35086f59de1STim Keith!  procedure :: s
35186f59de1STim Keith! end interface
35286f59de1STim Keith!contains
35386f59de1STim Keith! subroutine s(x)
35486f59de1STim Keith!  integer(4) :: x
35586f59de1STim Keith! end
35686f59de1STim Keith!end
35786f59de1STim Keith
35886f59de1STim Keithmodule m7b
35986f59de1STim Keith  interface g_real
36086f59de1STim Keith    module procedure s
36186f59de1STim Keith  end interface
36286f59de1STim Keith  private :: s
36386f59de1STim Keithcontains
36486f59de1STim Keith  subroutine s(x)
36586f59de1STim Keith    real :: x
36686f59de1STim Keith  end subroutine
36786f59de1STim Keithend
36886f59de1STim Keith!Expect: m7b.mod
36986f59de1STim Keith!module m7b
370*a3e9d3c2SPeter Klausler! private :: s
37186f59de1STim Keith! interface g_real
37286f59de1STim Keith!  procedure :: s
37386f59de1STim Keith! end interface
37486f59de1STim Keith!contains
37586f59de1STim Keith! subroutine s(x)
37686f59de1STim Keith!  real(4) :: x
37786f59de1STim Keith! end
37886f59de1STim Keith!end
37986f59de1STim Keith
38086f59de1STim Keithmodule m7c
38186f59de1STim Keith  use m7a, only: g => g_integer
38286f59de1STim Keith  use m7b, only: g => g_real
38386f59de1STim Keith  interface g
38486f59de1STim Keith    module procedure s
38586f59de1STim Keith  end interface
38686f59de1STim Keith  private :: s
38786f59de1STim Keithcontains
38886f59de1STim Keith  subroutine s(x)
38986f59de1STim Keith    complex :: x
39086f59de1STim Keith  end subroutine
39186f59de1STim Keith  subroutine test()
39286f59de1STim Keith    real :: x
39386f59de1STim Keith    integer :: y
39486f59de1STim Keith    complex :: z
39586f59de1STim Keith    call g(x)
39686f59de1STim Keith    call g(y)
39786f59de1STim Keith    call g(z)
39886f59de1STim Keith  end
39986f59de1STim Keithend
40086f59de1STim Keith!Expect: m7c.mod
40186f59de1STim Keith!module m7c
40286f59de1STim Keith! use m7a, only: g => g_integer
4039b200074SPeter Klausler! use m7b, only: g => g_real
404*a3e9d3c2SPeter Klausler! private :: s
40586f59de1STim Keith! interface g
40686f59de1STim Keith!  procedure :: s
40786f59de1STim Keith! end interface
40886f59de1STim Keith!contains
40986f59de1STim Keith! subroutine s(x)
41086f59de1STim Keith!  complex(4) :: x
41186f59de1STim Keith! end
41286f59de1STim Keith! subroutine test()
41386f59de1STim Keith! end
41486f59de1STim Keith!end
41586f59de1STim Keith
41686f59de1STim Keith! Test m8 is like m7 but without renaming.
41786f59de1STim Keith
41886f59de1STim Keithmodule m8a
41986f59de1STim Keith  interface g
42086f59de1STim Keith    module procedure s
42186f59de1STim Keith  end interface
42286f59de1STim Keith  private :: s
42386f59de1STim Keithcontains
42486f59de1STim Keith  subroutine s(x)
42586f59de1STim Keith    integer :: x
42686f59de1STim Keith  end
42786f59de1STim Keithend
42886f59de1STim Keith!Expect: m8a.mod
42986f59de1STim Keith!module m8a
430*a3e9d3c2SPeter Klausler! private :: s
43186f59de1STim Keith! interface g
43286f59de1STim Keith!  procedure :: s
43386f59de1STim Keith! end interface
43486f59de1STim Keith!contains
43586f59de1STim Keith! subroutine s(x)
43686f59de1STim Keith!  integer(4) :: x
43786f59de1STim Keith! end
43886f59de1STim Keith!end
43986f59de1STim Keith
44086f59de1STim Keithmodule m8b
44186f59de1STim Keith  interface g
44286f59de1STim Keith    module procedure s
44386f59de1STim Keith  end interface
44486f59de1STim Keith  private :: s
44586f59de1STim Keithcontains
44686f59de1STim Keith  subroutine s(x)
44786f59de1STim Keith    real :: x
44886f59de1STim Keith  end subroutine
44986f59de1STim Keithend
45086f59de1STim Keith!Expect: m8b.mod
45186f59de1STim Keith!module m8b
452*a3e9d3c2SPeter Klausler! private :: s
45386f59de1STim Keith! interface g
45486f59de1STim Keith!  procedure :: s
45586f59de1STim Keith! end interface
45686f59de1STim Keith!contains
45786f59de1STim Keith! subroutine s(x)
45886f59de1STim Keith!  real(4) :: x
45986f59de1STim Keith! end
46086f59de1STim Keith!end
46186f59de1STim Keith
46286f59de1STim Keithmodule m8c
46386f59de1STim Keith  use m8a
46486f59de1STim Keith  use m8b
46586f59de1STim Keith  interface g
46686f59de1STim Keith    module procedure s
46786f59de1STim Keith  end interface
46886f59de1STim Keith  private :: s
46986f59de1STim Keithcontains
47086f59de1STim Keith  subroutine s(x)
47186f59de1STim Keith    complex :: x
47286f59de1STim Keith  end subroutine
47386f59de1STim Keith  subroutine test()
47486f59de1STim Keith    real :: x
47586f59de1STim Keith    integer :: y
47686f59de1STim Keith    complex :: z
47786f59de1STim Keith    call g(x)
47886f59de1STim Keith    call g(y)
47986f59de1STim Keith    call g(z)
48086f59de1STim Keith  end
48186f59de1STim Keithend
48286f59de1STim Keith!Expect: m8c.mod
48386f59de1STim Keith!module m8c
48486f59de1STim Keith! use m8a, only: g
4859b200074SPeter Klausler! use m8b, only: g
486*a3e9d3c2SPeter Klausler! private :: s
48786f59de1STim Keith! interface g
48886f59de1STim Keith!  procedure :: s
48986f59de1STim Keith! end interface
49086f59de1STim Keith!contains
49186f59de1STim Keith! subroutine s(x)
49286f59de1STim Keith!  complex(4) :: x
49386f59de1STim Keith! end
49486f59de1STim Keith! subroutine test()
49586f59de1STim Keith! end
49686f59de1STim Keith!end
49786f59de1STim Keith
49886f59de1STim Keith! Merging a use-associated generic with a local generic
49986f59de1STim Keith
50086f59de1STim Keithmodule m9a
50186f59de1STim Keith  interface g
50286f59de1STim Keith    module procedure s
50386f59de1STim Keith  end interface
50486f59de1STim Keith  private :: s
50586f59de1STim Keithcontains
50686f59de1STim Keith  subroutine s(x)
50786f59de1STim Keith    integer :: x
50886f59de1STim Keith  end
50986f59de1STim Keithend
51086f59de1STim Keith!Expect: m9a.mod
51186f59de1STim Keith!module m9a
512*a3e9d3c2SPeter Klausler! private :: s
51386f59de1STim Keith! interface g
51486f59de1STim Keith!  procedure :: s
51586f59de1STim Keith! end interface
51686f59de1STim Keith!contains
51786f59de1STim Keith! subroutine s(x)
51886f59de1STim Keith!  integer(4) :: x
51986f59de1STim Keith! end
52086f59de1STim Keith!end
52186f59de1STim Keith
52286f59de1STim Keithmodule m9b
52386f59de1STim Keith  use m9a
52486f59de1STim Keith  interface g
52586f59de1STim Keith    module procedure s
52686f59de1STim Keith  end interface
52786f59de1STim Keith  private :: s
52886f59de1STim Keithcontains
52986f59de1STim Keith  subroutine s(x)
53086f59de1STim Keith    real :: x
53186f59de1STim Keith  end
53286f59de1STim Keith  subroutine test()
53386f59de1STim Keith    call g(1)
53486f59de1STim Keith    call g(1.0)
53586f59de1STim Keith  end
53686f59de1STim Keithend
53786f59de1STim Keith!Expect: m9b.mod
53886f59de1STim Keith!module m9b
53986f59de1STim Keith! use m9a,only:g
540*a3e9d3c2SPeter Klausler! private::s
54186f59de1STim Keith! interface g
54286f59de1STim Keith!   procedure::s
54386f59de1STim Keith! end interface
54486f59de1STim Keith!contains
54586f59de1STim Keith! subroutine s(x)
54686f59de1STim Keith!   real(4)::x
54786f59de1STim Keith! end
54886f59de1STim Keith! subroutine test()
54986f59de1STim Keith! end
55086f59de1STim Keith!end
55186f59de1STim Keith
5527082de56STim Keith! Verify that equivalent names are used when generic operators are merged
5537082de56STim Keith
5547082de56STim Keithmodule m10a
5557082de56STim Keith  interface operator(.ne.)
5567082de56STim Keith  end interface
5577082de56STim Keithend
5587082de56STim Keith!Expect: m10a.mod
5597082de56STim Keith!module m10a
5607082de56STim Keith! interface operator(.ne.)
5617082de56STim Keith! end interface
5627082de56STim Keith!end
5637082de56STim Keith
5647082de56STim Keithmodule m10b
5657082de56STim Keith  interface operator(<>)
5667082de56STim Keith  end interface
5677082de56STim Keithend
5687082de56STim Keith!Expect: m10b.mod
5697082de56STim Keith!module m10b
5707082de56STim Keith! interface operator(<>)
5717082de56STim Keith! end interface
5727082de56STim Keith!end
5737082de56STim Keith
5747082de56STim Keithmodule m10c
5757082de56STim Keith  use m10a
5767082de56STim Keith  use m10b
5777082de56STim Keith  interface operator(/=)
5787082de56STim Keith  end interface
5797082de56STim Keithend
5807082de56STim Keith!Expect: m10c.mod
5817082de56STim Keith!module m10c
5827082de56STim Keith! use m10a,only:operator(.ne.)
5839b200074SPeter Klausler! use m10b,only:operator(.ne.)
5847082de56STim Keith! interface operator(.ne.)
5857082de56STim Keith! end interface
5867082de56STim Keith!end
5877082de56STim Keith
5887082de56STim Keithmodule m10d
5897082de56STim Keith  use m10a
5907082de56STim Keith  use m10c
5917082de56STim Keith  private :: operator(<>)
5927082de56STim Keithend
5937082de56STim Keith!Expect: m10d.mod
5947082de56STim Keith!module m10d
5957082de56STim Keith! use m10a,only:operator(.ne.)
5969b200074SPeter Klausler! use m10c,only:operator(.ne.)
5977082de56STim Keith! interface operator(.ne.)
5987082de56STim Keith! end interface
5997082de56STim Keith! private::operator(.ne.)
6007082de56STim Keith!end
601d6acf3c2STim Keith
602d6acf3c2STim Keithmodule m11a
603d6acf3c2STim Keithcontains
604d6acf3c2STim Keith  subroutine s1()
605d6acf3c2STim Keith  end
606d6acf3c2STim Keithend
607d6acf3c2STim Keith!Expect: m11a.mod
608d6acf3c2STim Keith!module m11a
609d6acf3c2STim Keith!contains
610d6acf3c2STim Keith! subroutine s1()
611d6acf3c2STim Keith! end
612d6acf3c2STim Keith!end
613d6acf3c2STim Keith
614d6acf3c2STim Keithmodule m11b
615d6acf3c2STim Keith  use m11a
616d6acf3c2STim Keith  interface g
617d6acf3c2STim Keith    module procedure s1
618d6acf3c2STim Keith  end interface
619d6acf3c2STim Keithend
620d6acf3c2STim Keith!Expect: m11b.mod
621d6acf3c2STim Keith!module m11b
622d6acf3c2STim Keith! use m11a,only:s1
623d6acf3c2STim Keith! interface g
624d6acf3c2STim Keith!  procedure::s1
625d6acf3c2STim Keith! end interface
626d6acf3c2STim Keith!end
627*a3e9d3c2SPeter Klausler
628*a3e9d3c2SPeter Klauslermodule m12
629*a3e9d3c2SPeter Klausler  interface generic
630*a3e9d3c2SPeter Klausler    module procedure specific
631*a3e9d3c2SPeter Klausler  end interface
632*a3e9d3c2SPeter Klausler  interface
633*a3e9d3c2SPeter Klausler    module subroutine s(a1,a2)
634*a3e9d3c2SPeter Klausler      character(*) a1
635*a3e9d3c2SPeter Klausler      character(generic(a1)) a2
636*a3e9d3c2SPeter Klausler    end
637*a3e9d3c2SPeter Klausler  end interface
638*a3e9d3c2SPeter Klausler contains
639*a3e9d3c2SPeter Klausler  pure integer function specific(x)
640*a3e9d3c2SPeter Klausler    character(*), intent(in) :: x
641*a3e9d3c2SPeter Klausler    specific = len(x)
642*a3e9d3c2SPeter Klausler  end
643*a3e9d3c2SPeter Klauslerend
644*a3e9d3c2SPeter Klausler!Expect: m12.mod
645*a3e9d3c2SPeter Klausler!module m12
646*a3e9d3c2SPeter Klausler! interface
647*a3e9d3c2SPeter Klausler!  module subroutine s(a1,a2)
648*a3e9d3c2SPeter Klausler!   character(*,1)::a1
649*a3e9d3c2SPeter Klausler!   character(specific(a1),1)::a2
650*a3e9d3c2SPeter Klausler!  end
651*a3e9d3c2SPeter Klausler! end interface
652*a3e9d3c2SPeter Klausler! interface generic
653*a3e9d3c2SPeter Klausler!  procedure::specific
654*a3e9d3c2SPeter Klausler! end interface
655*a3e9d3c2SPeter Klausler!contains
656*a3e9d3c2SPeter Klausler! pure function specific(x)
657*a3e9d3c2SPeter Klausler!  character(*,1),intent(in)::x
658*a3e9d3c2SPeter Klausler!  integer(4)::specific
659*a3e9d3c2SPeter Klausler! end
660*a3e9d3c2SPeter Klausler!end
661