! { dg-do run } ! ! Test the fix for pr88735 in which non-finalizable entities were being ! finalized because they had finalizable components and 'var' in defined ! assignments was being finalized. ! ! Contributed by Martin Stein ! module mod implicit none type, public :: t integer, allocatable :: i contains procedure, public :: set generic, public :: assignment(=) => set final :: finalise end type t integer, public :: final_count = 0 contains subroutine set(self, x) class(t), intent(inout) :: self class(t), intent(in) :: x if (allocated(x%i)) then self%i = x%i self%i = self%i + 1 end if end subroutine set subroutine finalise(self) type(t), intent(inout) :: self if (allocated(self%i)) then final_count = final_count + 1 deallocate(self%i) end if end subroutine finalise end module mod program finalise_assign use mod implicit none type :: s type(t) :: x end type s type(s) :: a, b type(t) :: c a%x%i = 123 ! Produces no final calls because 'b' is not a 'finalizable entity'. b = a if (final_count /= 0) stop 1 ! Produces no final calls because this is a defined assignment. c = a%x if (final_count /= 0) stop 2 end program finalise_assign