ieee_9.f90: XFAIL on arm*-*-gnueabi[hf].
[official-gcc.git] / gcc / testsuite / gfortran.dg / typebound_operator_11.f90
blobb37e975211306ddb2a2858f278f29c0bf46ed7c3
1 ! { dg-do compile }
3 ! PR fortran/46328
5 ! Contributed by Damian Rouson
7 module foo_module
8 type ,abstract :: foo
9 contains
10 procedure(t_interface) ,deferred :: t
11 procedure(assign_interface) ,deferred :: assign
12 procedure(multiply_interface) ,deferred :: multiply
13 generic :: operator(*) => multiply
14 generic :: assignment(=) => assign
15 end type
16 abstract interface
17 function t_interface(this)
18 import :: foo
19 class(foo) :: this
20 class(foo), allocatable ::t_interface
21 end function
22 function multiply_interface(lhs,rhs)
23 import :: foo
24 class(foo), allocatable :: multiply_interface
25 class(foo), intent(in) :: lhs
26 real, intent(in) :: rhs
27 end function
28 subroutine assign_interface(lhs,rhs)
29 import :: foo
30 class(foo), intent(in) :: rhs
31 class(foo), intent(inout) :: lhs
32 end subroutine
33 end interface
34 contains
35 subroutine bar(x,dt)
36 class(foo) :: x
37 real, intent(in) :: dt
38 x = x%t()*dt
39 end subroutine
40 end module