view gcc/testsuite/gfortran.dg/pr38351.f90 @ 145:1830386684a0

gcc-9.2.0
author anatofuz
date Thu, 13 Feb 2020 11:34:05 +0900
parents 84e7813d76e9
children
line wrap: on
line source

! { dg-do compile }
module m1
   type t1
      integer :: i
   end type t1
   interface operator(+)
      module procedure add
   end interface
   contains
      type(t1) function add(a,b)
         type(t1), intent(in) :: a,b
      end function
end module m1

program foo
   use m1
   type(t1), dimension(2,2) :: a = t1(1), b = t1(2)
   type(t1) :: c=t1(1), d=t1(2)
   c = c + d
   a = a + b   ! { dg-error "Unexpected derived-type entities" }
end program foo