Imported Upstream version 4.7.2
[platform/upstream/gcc48.git] / gcc / testsuite / gfortran.dg / typebound_operator_10.f03
1 ! { dg-do compile }
2 ! PR51791 and original testcase for PR46328.
3 !
4 ! Contributer by Thomas Koenig  <tkoenig@gcc.gnu.org>
5 !
6 module field_module
7   implicit none
8   type ,abstract :: field
9   contains
10     procedure(field_op_real) ,deferred :: multiply_real
11     generic :: operator(*) => multiply_real
12   end type
13   abstract interface
14     function field_op_real(lhs,rhs)
15       import :: field
16       class(field) ,intent(in)  :: lhs
17       real ,intent(in) :: rhs
18       class(field) ,allocatable :: field_op_real
19     end function
20   end interface
21 end module
22
23 program main
24   use field_module
25   implicit none
26   class(field) ,pointer :: u
27   u = (u)*2. ! { dg-error "check that there is a matching specific" }
28 end program
29 ! { dg-final { cleanup-modules "field_module" } }