Double finalization on assignment

As follow-up of an earlier discussion (Should we avoid assignment of derived types in robust programs?) I am trying to understand the consequences of finalization on assignment, if a derived type without finalization and without defined assignment contains an other derived type with finalization and with defined assignment.

In a nutshell (minimal working example can be found below), the problem boils down to the question, how often the finalizer of the contained derived type component should be invoked on (intrinsic) assignment between instances of the containing derived type.


type :: TInternal
.. ! Type with defined assignment and defined finalization
end type TInternal

type TWrapper
  type(TInternal) :: internal
end type TWrapper

type(TWrapper) :: wrapper, wrapper2

! How often should the finalizer of the TInternal component be called here (and on which instances)?
wrapper2 = wrapper
Minimal working example
module internal_module
  implicit none

  type :: TInternal
    integer :: id = 0
  contains
    procedure :: assign => TInternal_assign
    generic :: assignment(=) => assign
    final :: TInternal_final
  end type TInternal

contains

  subroutine TInternal_init(this, id)
    type(TInternal), intent(out) :: this
    integer, intent(in) :: id

    this%id = id
    print "(A, I2)", "TInternal_init: id:", id

  end subroutine TInternal_init


  subroutine TInternal_final(this)
    type(TInternal), intent(inout) :: this

    print "(A, I2)", "TInternal_final, id:", this%id
    if (this%id > 0) then
      this%id = -1
    else if (this%id < 0) then
      this%id = this%id - 1
    end if

  end subroutine TInternal_final


  subroutine TInternal_assign(this, other)
    class(TInternal), intent(out) :: this
    type(TInternal), intent(in) :: other

    print "(A, I2, A, I2)", "TInternal_assign: this%id:", this%id, ", other%id:", other%id
    this%id = other%id

  end subroutine TInternal_assign

end module internal_module


program reftest
  use internal_module
  implicit none

  type :: TWrapper
    type(TInternal) :: internal
  end type TWrapper

  type(TWrapper) :: wrapper, wrapper2

  call TInternal_init(wrapper%internal, 1)
  call TInternal_init(wrapper2%internal, 2)
  print "(A)", "-> Assignment"
  wrapper2 = wrapper

end program reftest

The two compilers I tend to trust most for this feature (the two compilers where I don’t have assignment related pending bug reports), finalize the type(TInternal) component twice, by first finalizing the instance and then calling the finalizer on the finalized instance again. Does anybody know, whether this is the supposed behavior? (I have problems to find the motivation of this behavior in the standard.)

Also, one of the two compilers uses the “doubly” finalized type(TInternal) component as LHS-argument within the assignment subroutine, while the other compiler a default-initialized type(TInternal) component. (See the output below). Former seems to be a bug to me, isn’t it? (For an intent(out) dummy argument, I would intuitively expect to find a default initialized instance after entering the subroutine.)

Does anybody have a deeper view on this issue?

The relevant output of the two compilers is follows:

...
-> Assignment
TInternal_final, id: 2
TInternal_final, id:-1
TInternal_assign: this%id:-2, other%id: 1

versus

...
-> Assignment
-> Assignment
TInternal_final, id: 2
TInternal_final, id:-1
TInternal_assign: this%id: 0, other%id: 1
1 Like

I think the finalizations are happening in a different way than you are thinking. The only finalizations I see that should occur in this program are due to the intent(out) arguments of the procedures in internal_module. call TInternal_init(wrapper%internal, 1) should cause wrapper%internal to be finalized. Then call TInternal_init(wrapper%internal, 1) should cause wrapper2%internal to be finalized. Finally, wrapper2 = wrapper should cause wrapper2%internal to be finalized. In the case of the first two finalizations, the value of this%id should actually be undefined. I would expect a standards conforming compiler to output the following, where I’ve used question marks for the undefined values, but your compiler will likely output 0, or some random integer.

TInternal_final, id: ?
TInternal_init: id: 1
TInternal_final, id: ?
TInternal_init: id: 2
-> Assignment
TInternal_final, id: 2
TInternal_assign: this%id: ?, other%id: 1

Note that no finalization of wrapper or wrapper2 occurs at the end of the program, as dictated by the standard.

Also note, it is not defined whether the value assigned to wrapper2%internal%id in the finalization gets carried over to the defined assignment, hence my use of the ? in the expected output.

EDIT: I hadn’t noticed the default initialization of id. Those question marks should all be 0.

I have been informed I missed a finalization, and that the assignment does in fact invoke finalization of wrapper2%internal twice.

The intrinsic assignment finalizes wrapper2, which invokes finalization of wrapper2%internal. Then, invocation of defined assignment for wrapper2%internal again finalizes it, due to the intent(out). Relevant sections of the standard include, 7.5.6.3p1, 7.5.6.2(2), 7.5.6.3p7.

With that, and correction for the default initialization of id, I believe the expected output should be as follows.

TInternal_final, id: 0
TInternal_init: id: 1
TInternal_final, id: 0
TInternal_init: id: 2
-> Assignment
TInternal_final, id: 2
TInternal_final, id: -1
TInternal_assign: this%id: 0, other%id: 1

Please note the compiler in question with this output has pending bug requests with me at their support center with default initialization and with clearing out memory with objects in undefined state and such. I have not studied this case but I suspect that is why the strange -2 value shows up in the output.

I suspect no compiler at present is anywhere close to 100% robust when it comes to finalization including with assignments, though one of the two compilers here might be close to getting there.

The standard is the best recourse here but it too might need interpretation requests when it comes to certain cases that might be on the edge of what was thought through with the documented semantics.