modula2: Simplify REAL/LONGREAL/SHORTREAL node creation.
[official-gcc.git] / gcc / testsuite / gfortran.dg / typebound_operator_16.f03
blobf56301cfd15ffbb504940182ecd13c7558087299
1 ! { dg-do compile }
3 ! PR 49591: [OOP] Multiple identical specific procedures in type-bound operator not detected
5 ! This is interpretation request F03/0018:
6 ! http://www.j3-fortran.org/doc/meeting/195/11-214.txt
8 ! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
10 module M1
11   type T
12     integer x
13   contains
14     procedure :: MyAdd_t => myadd
15     generic :: operator(+) => myAdd_t
16   end type T
17   type X
18     real q
19   contains
20     procedure, pass(b) :: MyAdd_x => myadd
21     generic :: operator(+) => myAdd_x       ! { dg-error "is already present in the interface" }
22   end type X
23 contains
24   integer function MyAdd ( A, B )
25     class(t), intent(in) :: A
26     class(x), intent(in) :: B
27     myadd = a%x + b%q
28   end function MyAdd
29 end module
31 module M2
32   interface operator(+)
33     procedure MyAdd
34   end interface
35   type T
36     integer x
37   contains
38     procedure :: MyAdd_t => myadd
39     generic :: operator(+) => myAdd_t  ! { dg-error "is already present in the interface" }
40   end type T
41 contains
42   integer function MyAdd ( A, B )
43     class(t), intent(in) :: A
44     real, intent(in) :: B
45     myadd = a%x + b
46   end function MyAdd
47 end module