OSDN Git Service

2010-04-06 Tobias Burnus <burnus@net-b.de>
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / interface_assignment_5.f90
1 ! { dg-do compile }
2 !
3 ! PR 42677: [4.5 Regression] Bogus Error: Ambiguous interfaces '...' in intrinsic assignment operator
4 !
5 ! Contributed by Harald Anlauf <anlauf@gmx.de>
6
7 module mod1
8   implicit none
9   type t_m
10      integer :: i = 0
11   end type t_m
12 !------------------------------------------------------------------------------
13   interface assignment (=)
14      module procedure assign_m
15   end interface
16 !------------------------------------------------------------------------------
17 contains
18   subroutine assign_m (y, x)
19     type(t_m) ,intent(inout) :: y
20     type(t_m) ,intent(in)    :: x
21   end subroutine assign_m
22 end module mod1
23 !==============================================================================
24 module mod2
25   use mod1, only: t_m, assignment(=)
26   implicit none
27   type t_atm
28      integer :: k
29   end type t_atm
30 !------------------------------------------------------------------------------
31   interface assignment(=)
32      module procedure assign_to_atm
33   end interface
34 !------------------------------------------------------------------------------
35   interface
36      pure subroutine delete_m (x)
37        use mod1
38        type(t_m) ,intent(in) :: x
39      end subroutine delete_m
40   end interface
41 !------------------------------------------------------------------------------
42 contains
43   subroutine assign_to_atm (atm, r)
44     type(t_atm) ,intent(inout) :: atm
45     integer     ,intent(in)    :: r
46   end subroutine assign_to_atm
47 end module mod2
48  
49 ! { dg-final { cleanup-modules "mod1 mod2" } }