OSDN Git Service

* config/i386/i386.md (UNSPEC_VSIBADDR): New.
[pf3gnuchains/gcc-fork.git] / gcc / testsuite / gfortran.dg / host_assoc_function_5.f90
1 ! { dg-do compile }
2 !
3 ! PR fortran/38665, in which checking for host association
4 ! was wrongly trying to substitute mod_symmon(mult) with
5 ! mod_sympoly(mult) in the user operator expression on line
6 ! 43.
7 !
8 ! Contributed by Thomas Koenig <tkoenig@gcc.gnu.org>
9 !
10 module mod_symmon
11  implicit none
12
13  public :: t_symmon, operator(*)
14  private
15
16  type t_symmon
17    integer :: ierr = 0
18  end type t_symmon
19
20  interface operator(*)
21    module procedure mult
22  end interface
23
24 contains
25  elemental function mult(m1,m2) result(m)
26   type(t_symmon), intent(in) :: m1, m2
27   type(t_symmon) :: m
28  end function mult
29 end module mod_symmon
30
31 module mod_sympoly
32  use mod_symmon
33  implicit none
34
35  type t_sympol
36    type(t_symmon), allocatable :: mons(:)
37  end type t_sympol
38 contains
39
40  elemental function mult(p1,p2) result(p)
41   type(t_sympol), intent(in) :: p1,p2
42   type(t_sympol) :: p
43   type(t_symmon), allocatable :: mons(:)
44   mons(1) = p1%mons(1)*p2%mons(2)
45  end function
46 end module
47 ! { dg-final { cleanup-modules "mod_symmon mod_sympoly" } }