blob: 6e6dc52d0fdc318e0cbf6ade47e34984531591a7 [file] [log] [blame]
! { dg-do compile }
!
! PR 46952: [OOP] Spurious "recursive call" error with type bound procedure
!
! Contributed by Ian Harvey <ian_harvey@bigpond.com>
module m
type, abstract :: t
contains
procedure(inter), pass, deferred :: foo
end type
contains
subroutine inter(this)
class(t) :: this
call this%foo()
end subroutine inter
end module m
! { dg-final { cleanup-modules "m" } }