8

Modern Fortran contains various object-oriented ideas, including a concepts of "destructors" through the FINAL keyword.

MODULE mobject
  TYPE :: tobject
    ! Data declarations
  CONTAINS
    FINAL :: finalize
  END TYPE
CONTAINS
  SUBROUTINE finalize(object)
    TYPE(tobject) object
    ...
  END SUBROUTINE
END MODULE

However, is this feature reliable? Notably, I noticed inconsistencies about when, and whether at all, it will be called, with major differences between Intel Fortran 19 and GFortan 7, 8:

  • GFortran fails to destroy objects stored inside arrays.
  • Intel Fortran:
    • performs spurious and potentially superfluos destructions upon assignment, potentially even on memory containing junk data, and
    • performs a spurious call to the destructor upon returning from a function.

I noticed no difference between gfortran-7.4.0 and gfortran-8.2.1.2.

These inconsistencies raise some questions about the practical usability of destructors for me. Is either of the behaviors fully conforming with the standard? Is the standard unclear on this? Does the standard maybe contain clauses, that lead to unintuitive behavior?

Detailed analysis (code see below)

  • PROGRAM Block. Gfortran will not call the destructor for instances declared in the PROGRAM block, while Ifort will (see run1 in example).

  • Scalar objects. For instances declared as scalars, both Gfortran and IFort will call the destructor, if the variable has seen any form of initialization. Intel Fortran however, when assigning a function return value, will call it also

    • on the uninitialzied object on the stack before overwriting it with the data from the function, and
    • seemingly at the end of the newObject function.

    This can however be guarded against by explicitly checking whether the object is initialized, before performing any cleanup.

This means, that the programmer has to explicitly check, if the instance has been initialized.

  • Objects in arrays. If the object is contain in an array, and the array goes out of scope,

    • Gfortran will not invoke the destructor.
    • Intel Fortran may invoke the destructor, depending on how a given array member was initialized.
    • It makes no difference, whether the array is declared allocatable.
  • Allocatable array initialized by assignment. When using the modern feature, where assignment to an allocatable array implies allocation, the same holds, except that there are no uninitialzied instances upon which IntelFortran can call the destructor.

  • Allocatable/Pointers from functions.

    • GFortran doesn't call the destructor at the end of the function returning the an allocatable object or a pointer to an object, and instead calls it when the value is deallocated in the client code, explicitly or by going out of scope for allocatables. That's what I expected.
    • Intel Fortran calls in some additional cases:
      • When the object is declared allocatable, but not when it is a pointer, Intel Fortran invokes the destructor on the local value of the function upon exiting the function.
      • When initializing the object inside the function with implied allocation (var = newObject(...)), or in the case of the pointer variant, with explicit allocation (allocate(var); var = newObject(...)), the destructor is invoked on uninitialized memory, visible in run5MoveAlloc and run6MovePtr from %name containing junk data. This can be resolved by using the allocate(var); call var%init(...) pattern instead.

Testing Code

!! -- Makefile ---------------------------------------------------
!! Runs the code with various compilers.

SHELL = bash
FC = NO_COMPILER_SPECIFIED
COMPILERS = gfortran-7 gfortran-8 ifort
PR = @echo$(n)pr -m -t -w 100

define n


endef

all: 
    rm -rf *.mod *.bin
    $(foreach FC, $(COMPILERS), $(n)\
      rm -rf *.mod && \
      $(FC) destructor.f90 -o $(FC).bin && \
      chmod +x $(FC).bin)
    $(PR) $(foreach FC, $(COMPILERS), <(head -1 <($(FC) --version)))
    $(info)
    $(foreach N,0 1 2 3 4 5 6,$(n) \
      $(PR) $(foreach FC, $(COMPILERS), <(./$(FC).bin $(N))))



!! -- destructor.f90 ---------------------------------------------

module mobject
  implicit none
  private
  public tobject, newObject

  type :: tobject
     character(32) :: name = "<undef>"
   contains
     procedure :: init
     final :: finalize
  end type tobject

contains

  subroutine init(object, name)
    class(tobject), intent(inout) :: object
    character(*), intent(in) :: name
    print *, "+ ", name
    object%name = name
  end subroutine init

  function newObject(name)
    type(tobject) :: newObject
    character(*), intent(in) :: name
    call new%init(name)
  end function newObject

  subroutine finalize(object)
    type(tobject) :: object
    print *, "- ", object%name
  end subroutine finalize

end module mobject



module mrun
  use mobject
  implicit none
contains

  subroutine run1()
    type(tobject) :: o1_uninit, o2_field_assigned, o3_tobject, o4_new, o6_init
    type(tobject), allocatable :: o5_new_alloc, o7_init_alloc
    print *, ">>>>> run1"
    o2_field_assigned%name = "o2_field_assigned"
    o3_tobject = tobject("o3_tobject")
    o4_new = newObject("o4_new")
    o5_new_alloc = newObject("o5_new_alloc")
    call o6_init%init("o6_init")
    allocate(o7_init_alloc)
    call o7_init_alloc%init("o7_init_alloc")
    print *, "<<<<< run1"
  end subroutine run1

  subroutine run2Array()
    type(tobject) :: objects(4)
    print *, ">>>>> run2Array"
    objects(1)%name = "objects(1)_uninit"
    objects(2) = tobject("objects(2)_tobject")
    objects(3) = newObject("objects(3)_new")
    call objects(4)%init("objects(4)_init")
    print *, "<<<<< run2Array"
  end subroutine run2Array

  subroutine run3AllocArr()
    type(tobject), allocatable :: objects(:)
    print *, ">>>>> run3AllocArr"
    allocate(objects(4))
    objects(1)%name = "objects(1)_uninit"
    objects(2) = tobject("objects(2)_tobject")
    objects(3) = newObject("objects(3)_new")
    call objects(4)%init("objects(4)_init")
    print *, "<<<<< run3AllocArr"
  end subroutine run3AllocArr

  subroutine run4AllocArrAssgn()
    type(tobject), allocatable :: objects(:)
    print *, ">>>>> run4AllocArrAssgn"
    objects = [ &
         tobject("objects(1)_tobject"), &
         newObject("objects(2)_new") ]
    print *, "<<<<< run4AllocArrAssgn"
  end subroutine run4AllocArrAssgn

  subroutine run5MoveAlloc()
    type(tobject), allocatable :: o_alloc
    print *, ">>>>> run5MoveAlloc"
    o_alloc = getAlloc()
    print *, "<<<<< run5MoveAlloc"
  end subroutine run5MoveAlloc

  function getAlloc() result(object)
    type(tobject), allocatable :: object
    print *, ">>>>> getAlloc"
    allocate(object)
    object = newObject("o_alloc")
    print *, "<<<<< getAlloc"
  end function getAlloc

  subroutine run6MovePtr()
    type(tobject), pointer :: o_pointer
    print *, ">>>>> run6MovePtr"
    o_pointer => getPtr()
    deallocate(o_pointer)
    print *, "<<<<< run6MovePtr"
  end subroutine run6MovePtr

  function getPtr() result(object)
    type(tobject), pointer :: object
    print *, ">>>>> getPtr"
    allocate(object)
    object = newObject("o_pointer")
    print *, "<<<<< getPtr"
  end function getPtr

end module mrun



program main
  use mobject
  use mrun
  implicit none
  type(tobject) :: object
  character(1) :: argument

  print *, ">>>>> main"
  call get_command_argument(1, argument)
  select case (argument)
  case("1")
     call run1()
  case("2")
     call run2Array()
  case("3")
     call run3AllocArr()
  case("4")
     call run4AllocArrAssgn()
  case("5")
     call run5MoveAlloc()
  case("6")
     call run6MovePtr()
  case("0")
     print *, "####################";
     print *, ">>>>> runDirectlyInMain"
     object = newObject("object_in_main")
     print *, "<<<<< runDirectlyInMain"
  case default
     print *, "Incorrect commandline argument"
  end select
  print *, "<<<<< main"
end program main

Output of the testing code

>> make
rm -rf *.mod *.bin
rm -rf *.mod && gfortran-7 destructor.f90 -o gfortran-7.bin && chmod +x gfortran-7.bin  
rm -rf *.mod && gfortran-8 destructor.f90 -o gfortran-8.bin && chmod +x gfortran-8.bin  
rm -rf *.mod && ifort destructor.f90 -o ifort.bin && chmod +x ifort.bin

pr -m -t -w 100  <(head -1 <(gfortran-7 --version))  <(head -1 <(gfortran-8 --version))  <(head -1 <(ifort --version))
GNU Fortran (SUSE Linux) 7.4.0   GNU Fortran (SUSE Linux) 8.2.1 2 ifort (IFORT) 19.0.4.243 2019041

pr -m -t -w 100  <(./gfortran-7.bin 0)  <(./gfortran-8.bin 0)  <(./ifort.bin 0) 
 >>>>> main                       >>>>> main                       >>>>> main
 ####################             ####################             ####################
 >>>>> runDirectlyInMain          >>>>> runDirectlyInMain          >>>>> runDirectlyInMain
 + object_in_main                 + object_in_main                 + object_in_main
 <<<<< runDirectlyInMain          <<<<< runDirectlyInMain          - <undef>
 <<<<< main                       <<<<< main                       - object_in_main
                                                                   <<<<< runDirectlyInMain
                                                                   <<<<< main

pr -m -t -w 100  <(./gfortran-7.bin 1)  <(./gfortran-8.bin 1)  <(./ifort.bin 1) 
 >>>>> main                       >>>>> main                       >>>>> main
 >>>>> run1                       >>>>> run1                       >>>>> run1
 + o4_new                         + o4_new                         - <undef>
 + o5_new_alloc                   + o5_new_alloc                   + o4_new
 + o6_init                        + o6_init                        - <undef>
 + o7_init_alloc                  + o7_init_alloc                  - o4_new
 <<<<< run1                       <<<<< run1                       + o5_new_alloc
 - o7_init_alloc                  - o7_init_alloc                  - o5_new_alloc
 - o6_init                        - o6_init                        + o6_init
 - o5_new_alloc                   - o5_new_alloc                   + o7_init_alloc
 - o4_new                         - o4_new                         <<<<< run1
 - o3_tobject                     - o3_tobject                     - <undef>
 - o2_field_assigned              - o2_field_assigned              - o2_field_assigned
 <<<<< main                       <<<<< main                       - o3_tobject
                                                                   - o4_new
                                                                   - o6_init
                                                                   - o5_new_alloc
                                                                   - o7_init_alloc
                                                                   <<<<< main

pr -m -t -w 100  <(./gfortran-7.bin 2)  <(./gfortran-8.bin 2)  <(./ifort.bin 2) 
 >>>>> main                       >>>>> main                       >>>>> main
 >>>>> run2Array                  >>>>> run2Array                  >>>>> run2Array
 + objects(3)_new                 + objects(3)_new                 - <undef>
 + objects(4)_init                + objects(4)_init                + objects(3)_new
 <<<<< run2Array                  <<<<< run2Array                  - <undef>
 <<<<< main                       <<<<< main                       - objects(3)_new
                                                                   + objects(4)_init
                                                                   <<<<< run2Array
                                                                   <<<<< main

pr -m -t -w 100  <(./gfortran-7.bin 3)  <(./gfortran-8.bin 3)  <(./ifort.bin 3) 
 >>>>> main                       >>>>> main                       >>>>> main
 >>>>> run3AllocArr               >>>>> run3AllocArr               >>>>> run3AllocArr
 + objects(3)_new                 + objects(3)_new                 - <undef>
 + objects(4)_init                + objects(4)_init                + objects(3)_new
 <<<<< run3AllocArr               <<<<< run3AllocArr               - <undef>
 <<<<< main                       <<<<< main                       - objects(3)_new
                                                                   + objects(4)_init
                                                                   <<<<< run3AllocArr
                                                                   <<<<< main

pr -m -t -w 100  <(./gfortran-7.bin 4)  <(./gfortran-8.bin 4)  <(./ifort.bin 4) 
 >>>>> main                       >>>>> main                       >>>>> main
 >>>>> run4AllocArrAssgn          >>>>> run4AllocArrAssgn          >>>>> run4AllocArrAssgn
 + objects(2)_new                 + objects(2)_new                 + objects(2)_new
 <<<<< run4AllocArrAssgn          <<<<< run4AllocArrAssgn          - objects(2)_new
 <<<<< main                       <<<<< main                       <<<<< run4AllocArrAssgn
                                                                   <<<<< main

pr -m -t -w 100  <(./gfortran-7.bin 5)  <(./gfortran-8.bin 5)  <(./ifort.bin 5) 
 >>>>> main                       >>>>> main                       >>>>> main
 >>>>> run5MoveAlloc              >>>>> run5MoveAlloc              >>>>> run5MoveAlloc
 >>>>> getAlloc                   >>>>> getAlloc                   >>>>> getAlloc
 + o_alloc                        + o_alloc                        + o_alloc
 <<<<< getAlloc                   <<<<< getAlloc                   - `4�\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0
 <<<<< run5MoveAlloc              <<<<< run5MoveAlloc              - o_alloc
 - o_alloc                        - o_alloc                        <<<<< getAlloc
 <<<<< main                       <<<<< main                       - o_alloc
                                                                   <<<<< run5MoveAlloc
                                                                   - o_alloc
                                                                   <<<<< main

pr -m -t -w 100  <(./gfortran-7.bin 6)  <(./gfortran-8.bin 6)  <(./ifort.bin 6)
 >>>>> main                       >>>>> main                       >>>>> main
 >>>>> run6MovePtr                >>>>> run6MovePtr                >>>>> run6MovePtr
 >>>>> getPtr                     >>>>> getPtr                     >>>>> getPtr
 + o_pointer                      + o_pointer                      + o_pointer
 <<<<< getPtr                     <<<<< getPtr                     - `��\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0\0
 - o_pointer                      - o_pointer                      - o_pointer
 <<<<< run6MovePtr                <<<<< run6MovePtr                <<<<< getPtr
 <<<<< main                       <<<<< main                       - o_pointer
                                                                   <<<<< run6MovePtr
                                                                   <<<<< main
kdb
  • 4,098
  • 26
  • 49

1 Answers1

6

TLDR: There are known outstanding issues in Gfortran. Intel claims full support. Some compilers claim no support.


The question about reliability and usability in general is quite subjective, because one has to consider many points that are unique to you (Do you need to support multiple compilers? Do you need to support their older versions? Which ones exactly? How critical it is if some entity is not finalized?).

You pose some claims which are hard to answer without actual code examples and may be a topic for a separate complete questions and answers. Gfortran publishes the current status of implementation of Fortran 2003 and 2008 features in this bug report https://gcc.gnu.org/bugzilla/show_bug.cgi?id=37336 (the link points to a meta-bug that points to several individual issues tracked in the bugzilla). It is known and that the feature is not finished and that there are outstanding issues. Most notably (at least for me), function results are not being finalized. An overview of the status of other compilers (simplified to Y/N/paritally) is at http://fortranwiki.org/fortran/show/Fortran+2003+status and used to be periodically updated in Fortran Forum articles.

I can't speak about those alleged spurious finalizations of Intel Fortran. If you identified a bug in your compiler, you should file a bug report with your vendor. Intel is generally quite responsive.

Some individual issues could be answered, though. You will likely find separate Q/As about them. But:

  • Gfortran will not call the destructor for instances declared in the PROGRAM block, while Ifort will (see run1 in example).

    • Variables declared in the main program implicitly acquire the save attribute according to the standard. The compiler is not supposed to generate any automatic finalization.
  • Intel Fortran however, when assigning a function return value, will call it also

    • As pointed out in the Gfortran bugzilla, gfortran does not finalize function result variables yet.
  • This means, that the programmer has to explicitly check, if the instance has been initialized.

    • I am afraid there is no such concept in the Fortran standard. I have no idea what " if the variable has seen any form of initialization" could mean. Note that an initializer function is a function like any other.
  • When using the modern feature, where assignment to an allocatable array implies allocation, the same holds, except that there are no uninitialzied instances upon which IntelFortran can call the destructor.

    • Not sure what that actually means. There isno such "initialization" in Fortran. Perhaps function results again?
  • Allocatable/Pointers from functions.

    • As pointed out several times, function results are not properly finalized in the current versions of Gfortran.

If you want any of the points to be answered in detail, you really have to ask a specific question. This one is too broad for that. The help/instructions for this site contain "Please edit the question to limit it to a specific problem with enough detail to identify an adequate answer. Avoid asking multiple distinct questions at once. See the [ask] for help clarifying this question."

  • About subjectivity, I don't quite see the problem. A destructor not being called short of a crash, or being called multiple times, should always raise a red flag. The simplest case I can think of is an object acting as proxy for buffered writing of files; It will hold a buffer and the filehandle (probably through a unit in fortran); Unexpected destruction will lead to crashes, and lack of destruction to lost data. Relevance of portability should be rather clear from asking about multiple implementations. – kdb Jan 30 '20 at 13:44
  • @kdb Sure it is a red flag. But *suitability for practical use* is subjective. And I have written why. There should not ever be finalization when there should not be one. But I am not aware of any such case. If you are, report it to your vendor. If you have some example, I am afraid it is lost among too many points of your question and in a code with too many options. You may want to ask a **specific question** about that single point. – Vladimir F Героям слава Jan 30 '20 at 13:47
  • @kdb Re portability, I have listed the status. What can we say more? You have to draw your specific conclusions. We really cannot say if it is currently portable enough for you. You have to decide that yourself. We can only list the outstanding issues and perhaps link the table in http://fortranwiki.org/fortran/show/Fortran+2003+status for other compilers. But we cannot say if it is portable enough for you. We can only say that some compilers do support it, some do not, some do partially. I am personally not using finalization in my main code. You have to decide yourself. – Vladimir F Героям слава Jan 30 '20 at 13:50
  • @kdb, I agree with Vladimir F: if you have a case where ifort in your code is doing finalization when it shouldn't then that's a problem. However, if your final subroutine is referencing a component (such as in `print *, "- ", object%name`) which is (potentially) not defined then that's a problem with your code, not with ifort/portability of finalization. – francescalus Jan 30 '20 at 13:58
  • @fracescalus Do the semantics according to the standard allow to return an object from a function without invoking the destructor at all? I would except, that at least a `pointer` could be returned without invoking the destructor. Returning an `allocatable` like that would be even more desirable, but that would require move semantics, which, as far as I know, aren't in the standard. – kdb Jan 30 '20 at 14:45
  • @VladimirF I see the point about the working being too aggressive to remain objective. I'll try to improve the question. – kdb Jan 30 '20 at 14:45
  • @kdb I think there is a time for asking a separate specific question about the issue discussed here in the comments. Do not rewrite questions that already received answers too much. – Vladimir F Героям слава Jan 30 '20 at 14:52
  • @kbd, the function result is treated similar to a local entity of the _function itself_. Please feel free to ask another question about the mechanics of finalization ([this other question](https://stackoverflow.com/q/29030497/3157076) may be relevant, and note that finalization in Fortran 2003 is "broken" and fixed in the current standard). – francescalus Jan 30 '20 at 15:37