Finalization/Copy in intrinsic polymorphic assignment

I am trying to understand the consequences of the polymorphic intrinsic assignment, especially, whether it can be warranted, that it always behaves move_alloc-like without creating (and finalizing) a temporary copy. I hope, somebody with deeper knowledge can comment on that.

The toy example below shows a container, which extends a basic type (which would normally contain the generic interface of that container type). The specific implementation stores its value in form of an allocated pointer and is created by making a polymorphic assignment, with a user defined structure constructor on its RHS. I find this solution very elegant, but I am wondering, whether I can rely on, that no temporary copy is made during this assignment (as its finalization would result in an invalid pointer).

module test
  implicit none

  type :: base_t
  end type base_t

  type, extends(base_t) :: ext_t
    integer, pointer :: ptr => null()
  contains
    final :: ext_final
  end type

  interface ext_t
    module procedure ext_construct
  end interface

contains

  function ext_construct(val) result(this)
    integer, intent(in) :: val
    type(ext_t) :: this
    allocate(this%ptr)
    this%ptr = val
  end function ext_construct


  subroutine ext_final(this)
    type(ext_t), intent(inout) :: this
    print *, "FINALIZER ext_final invoked"
    if (associated(this%ptr)) deallocate(this%ptr)
  end subroutine ext_final

end module test


program testprog
  use test
  implicit none

  class(base_t), allocatable :: base
  ! Is it warranted, that next line never makes a temporary copy
  ! and never triggers the finalizer of an ext_t instance?
  base = ext_t(42)
  print *, "ASSIGNMENT DONE"
  deallocate(base)

end program testprog

I know, that I could “enforce” the move_alloc like behavior by doing it explicitely:

type(ext_t), allocatable :: ext
class(base_t), allocatable :: base

allocate(ext)
call ext_init(ext, 42)   !<-- Needs an extra subroutine ext_init, which does the initialization
call move_alloc(ext, base)

but I find it less elegant and less expressive than the polymorphic assignment.

Alluded to by @rouson in his book “Scientific Software Design: The Object-Oriented Way”, there are some parallels with architectural design that can fascinate and enamor programmers with their own code designs and see elegance and beauty in their creations of “class” libraries and in the uses of them in client codes. Unfortunately the Fortran standard will soon prove a mirage, it will drain away most of such inspiration and it may even steer them away from Fortran altogether, or back toward the sequential procedural paradigm with low-level subroutine/function based APIs in their Fortran code.

As things stand,

  1. an intrinsic assignment per the Fortran standard is more like the equivalent of a shallow copy with derived type components with the POINTER attribute even though the intrinsic assignment otherwise behaves likes a deep copy instruction.
  2. the section on finalization in the standard calls for a conforming processor to finalize the function result in the nonpointer case. And a defined constructor is nothing but a generic interface to a function,
  3. the standard is effectively silent on matters such as temporaries and also with elision of function results. An assignment is obj = expr with the exp on RHS evaluated followed by the assignment. Thus a lot is left up to processor implementations and YMMY when it comes to quality of such implementations. Most compiler implementations are stuck somewhere between Fortran 2003 and 2008 revisions and failing to get this right for the practitioners.

Bottom-line: intrinsic assignment is unreliable for the case in the original post. There are few good options a coder can rely on other than explicit SUBROUTINE “APIs” where a library author takes great care to instantiate reliably the objects in question so the users can consume them safely e.g., the decidedly inelegant option

allocate( ext_t :: base )
! followed by
call base%init(..) ! if the base has a DEFERRED type-bound procedure for initialization;
! or more like, 
call init_ext(..) ! if the extension type module includes a suitable subroutine API
! or with procedure bound to extension type,
select type ( ext => base )
   type is ( ext_t )
      call ext%init( .. )
end select
1 Like

Thanks! Tthe inelegant solution is actually, how we do it currently. We never bind the init() to the type, though, as one would not be able to change its signature in extending types, but rather define a typename_init(this, ...) initializer subroutine for each non-abstract type.

The finalization issue seems to be unfortunately even more tricky as I thought. Not sure, whether it is the standard, which allows for various implementations, or just compilers, which do not implement the standard correctly. But, if change the program from above a little (and comment out the deallocate statement in the finalizer to avoid multiple deallocations), I get completely different results with 3 different compilers.

program testprog
  use test
  implicit none

  print *, "*** POLYMORPHIC ASSIGNMENT"
  block
    class(base_t), allocatable :: base
    ! Is it warranted, that next line never makes a temporary copy
    ! and never triggers the finalizer of an ext_t instance?
    base = ext_t(42)
    print *, "ASSIGNMENT DONE"
  end block
  print *, "BLOCK DONE"

  print *, "*** NON-POLYMORPHIC ASSIGNMENT TO ALLOCATABLE"
  block
    type(ext_t), allocatable :: ext

    ext = ext_t(42)
    print *, "ASSIGNMENT DONE"
  end block
  print *, "BLOCK DONE"

  print *, "*** NON-POLYMORPHIC ASSIGNMENT TO STATIC"
  block
    type(ext_t) :: ext

    ext = ext_t(42)
    print *, "ASSIGNMENT DONE"
  end block
  print *, "BLOCK DONE"

end program testprog

If I run the code above with NAG, GNU and INTEL, I obtain:

  • NAG (7.0)

     *** POLYMORPHIC ASSIGNMENT
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
     *** NON-POLYMORPHIC ASSIGNMENT TO ALLOCATABLE                                 
     FINALIZER ext_final invoked
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
     *** NON-POLYMORPHIC ASSIGNMENT TO STATIC                                      
     FINALIZER ext_final invoked
     FINALIZER ext_final invoked
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
    
  • GNU (10.x)

     *** POLYMORPHIC ASSIGNMENT
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
     *** NON-POLYMORPHIC ASSIGNMENT TO ALLOCATABLE                                 
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
     *** NON-POLYMORPHIC ASSIGNMENT TO STATIC                                      
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
    
  • Intel (2021)

     *** POLYMORPHIC ASSIGNMENT
     FINALIZER ext_final invoked
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
     *** NON-POLYMORPHIC ASSIGNMENT TO ALLOCATABLE
     FINALIZER ext_final invoked
     FINALIZER ext_final invoked
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
     *** NON-POLYMORPHIC ASSIGNMENT TO STATIC
     FINALIZER ext_final invoked
     FINALIZER ext_final invoked
     ASSIGNMENT DONE
     FINALIZER ext_final invoked
     BLOCK DONE
    

That means, the number of times a finalizer is invoked is not just scenario, but also highly compiler dependent: NAG (1, 2, 3), GFortran (1, 1, 1), Intel (2, 3, 3). Whether it is a “bug” in the standard or in the compilers, I don’t know, but one apparently really has to avoid assignment in general when using robust containers.

PS. Actually, I think, having robust containers is currently impossible for various other reasons as well, like the lack of the possibility to forbid copying (e.g via sourced allocation allocate(newcontainer, source=old_container_with_pointers)). So, we have to rely on programmers to read the library documentation of a container and to hope, they don’t do anything stupid with it, which they are not supposed to. The compiler won’t be a big help in enforcing that unfortunately…

2 Likes

I would argue vehemently it was indeed a bug in the standard starting Fortran 2003 (circa 2004) until Fortran 2008 Corrigenda (circa 2014):
http://isotc.iso.org/livelink/livelink?func=ll&objId=18597225&objAction=Open

There remain other issues with finalization in the current standard but that’s a separate matter.

Compiler implementations have mostly failed to notice the corrigenda though and are just waking up to the Fortran 2018 revision which took a long time for a minor revision to be published officially.

Consider a revised and simplified test of what’s shown in the previous comment:

Click for code

Revised checks toward finalization

module m

   type :: base_t
      character(len=50) :: name = "base_default"
   end type base_t

   type, extends(base_t) :: ext_t
   contains
      final :: ext_final
   end type

   interface ext_t
      module procedure ext_construct
   end interface

contains

   function ext_construct() result(this)
      type(ext_t) :: this
      this%name = "Constructor temporary (RHS expr)"
   end function ext_construct

   subroutine ext_final(this)
      type(ext_t), intent(inout) :: this
      print *, "FINALIZER ext_final invoked for ", trim(this%name)
   end subroutine ext_final

end module

program p

   use m

   print *, "*** POLYMORPHIC ASSIGNMENT"
   block
      class(base_t), allocatable :: base
      base = ext_t()
      select type ( ext => base )
         type is ( ext_t )
            ext%name = "block1::base"
      end select
      print *, "ASSIGNMENT DONE"
   end block
   print *, "BLOCK DONE"

   print *, "*** NON-POLYMORPHIC ASSIGNMENT TO ALLOCATABLE"
   block
      type(ext_t), allocatable :: ext
      ext = ext_t()
      ext%name = "block2::ext"
      print *, "ASSIGNMENT DONE"
   end block
   print *, "BLOCK DONE"

   print *, "*** NON-POLYMORPHIC ASSIGNMENT TO STATIC"
   block
      type(ext_t) :: ext
      ext = ext_t()
      ext%name = "block3::ext"
      print *, "ASSIGNMENT DONE"
   end block
   print *, "BLOCK DONE"

end program

Per my read of the standard, the expected output is as follows:

*** POLYMORPHIC ASSIGNMENT
FINALIZER ext_final invoked for RHS temporary construct
ASSIGNMENT DONE
FINALIZER ext_final invoked for block1::base
BLOCK DONE
*** NON-POLYMORPHIC ASSIGNMENT TO ALLOCATABLE
FINALIZER ext_final invoked for RHS temporary construct
ASSIGNMENT DONE
FINALIZER ext_final invoked for block2::ext
BLOCK DONE
*** NON-POLYMORPHIC ASSIGNMENT TO STATIC
FINALIZER ext_final invoked for base_default
FINALIZER ext_final invoked for RHS temporary construct
ASSIGNMENT DONE
FINALIZER ext_final invoked for block3::ext
BLOCK DONE

which is provided at least by Intel Fortran compiler version 18.0.5. IFORT since then has had a regression in one of their major releases which continues with their latest oneAPI 2021.4.

  • NAG compiler in the first block does not finalize the Constructor temporary i.e., the function result toward the RHS expr in the assignment which is nonconformant. NAG conforms in the second and third block.
  • IFORT one API 2021.4, in the second block, appears to finalize an undefined object, perhaps toward the undefined ext variable prior to assignment, which is nonconformant. IFORT appears to get other cases right.
  • gfortran is a work in progress. It does not finalize the function result toward the RHS expr in any of the 3 blocks which is nonconformant. It does not finalize the ext variable in the third block prior to assignment which is also nonconformant.
1 Like