Should associate trigger automatic finalization?

Consider the following program:

module associate_example

  implicit none

  type :: sparse
    integer :: colidx
    integer, allocatable :: rows(:)
    real, allocatable :: values(:)
  contains
    final :: finalize
  end type

contains

  subroutine finalize(this)
    type(sparse) :: this

    print *, "Finalizing column ", this%colidx
  end subroutine

end module associate_example

program associate_test

  use associate_example
  implicit none

  associate(s => sparse(3,[1,2,3],[5.,3.,8.]))

    print *, "In associate:"
    print *, s%colidx
    print *, s%rows
    print *, s%values

  end associate

  block
    type(sparse) :: s

    print *, "In block:"

    s = sparse(3,[1,2,3],[5.,3.,8.])

    print *, s%colidx
    print *, s%rows
    print *, s%values

  end block

end program

Both gfortran (v10.3) and ifort (v2021.4) compile the program without warnings. The output of gfortran is:

$ gfortran -Wall associate_test.f90 
$ ./a.out
munmap_chunk(): invalid pointer

Program received signal SIGABRT: Process abort signal.

The output of Intel Fortran is:

$ ifort -warn all associate_test.f90 
$ ./a.out
 In associate:
           3
           1           2           3
   5.000000       3.000000       8.000000    
 In block:
 Finalizing column            0
           3
           1           2           3
   5.000000       3.000000       8.000000    
 Finalizing column            3

I would expect finalization to occur at the end of the associate construct.

Is this mandated by the standard, or should we avoid associating with an expression that results in a derived type?

In the result from ifort, does the output line finalizing column 0 come from the finalization of the left-hand side in the assignment?

1 Like

If I overload the structure constructor by adding a custom constructor function:

  interface sparse
    module procedure new_sparse
  end interface
  function new_sparse(idx,rows,values) result(new)
    integer, intent(in) :: idx
    integer, intent(in) :: rows(:)
    real, intent(in) :: values(:)
    type(sparse) :: new

    new%colidx = idx
    allocate(new%rows,source=rows)
    allocate(new%values,source=values)

  end function

I get the behavior I expected:

$ ifort -warn all associate_test.f90 
(base) ipribec@ipribec-T530:~/fortran$ ./a.out
 In associate:
           3
           1           2           3
   5.000000       3.000000       8.000000    
 Finalizing column            3
 In block:
 Finalizing column            0
 Finalizing column            3
           3
           1           2           3
   5.000000       3.000000       8.000000    
 Finalizing column            3

In the case of gfortran, I have submitted several bug reports related to memory errors in the use of associate.

In the case of Intel, without the overloaded constructor, it looks as though some “optimizations” are being made, that may or may not be standards conforming. Perhaps someone with a more thorough understanding of this part of the standard could comment on whether this is allowed.

Per my understanding, the standard is silent on the question of the ASSOCIATE construct when the selector is an expression of a finalizable entity. Thus the chances are zero any of the compiler implementations will perform finalization in the first case shown here.

If finalization is important, then as a matter of good practice it does make sense to “avoid associating with an expression that results in a derived type.” But instead to make the selector an object that will be finalized as per the semantics stated in the standard.

Re: “the output line finalizing column 0,” it is the LHS in the assignment s = sparse(3, ..) in the BLOCK construct getting finalized as per the standard.

For the case where the structure constructor is used: no finalization should happen here at all, because use of the structure constructor is not one of the trigger cases.

For the case where a function overloads the structure constructor, the following text from the standard applies, I think:

F2018 / 7.5.6.3 when finalization occurs
…
If an executable construct references a nonpointer function, the result is finalized after execution of the innermost executable construct containing the reference.
…
which I take to mean that the finalizer must be executed once the ASSOCIATE block completes.

Regards
Reinhold

2 Likes

@Reinhold_Bader , welcome to the forum.

My hunch is compiler implementations will find the associate-stmt as not an executable construct and not do the finalization, that the instructions in the block part of the construct, the stuff between the associate-stmt and the end-associate-stmt is what they consider an executable-construct here.

1 Like

Maybe some people do, but the standard text does consider the associate-stmt as part of the associate-construct (F2018 / 11.1.3.1).

1 Like

@Reinhold_Bader thanks for joining the forum and your feedback!

Thanks Reinhold for the answer.

The example I constructed here is artificial in the sense that the derived type does not need a custom finalizer. However for any object which requires custom finalization (e.g. because it contains pointers) it’s probably a good idea to overload the structure constructor.

This seems very close to the programming idiom/pattern known as the “Rule of zero/three/five” in C++:

I agree. The structure constructor is so restricted in semantics that executing a finalizer is simply not necessary. But for the same reason, it usually cannot do what needs to be done for POINTER components.

Cheers.