Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Function constructors, pointers, and finalizers

Jacob_Williams
New Contributor I
1,083 Views

Consider the following code:

!********************************
module test_module

  implicit none

  type :: json_value
    integer :: i = 0
  end type json_value

  type :: json_file
    type(json_value),pointer :: p => null()
    contains
    procedure :: initialize
    final :: finalize_json_file
  end type json_file

  interface json_file
    module procedure :: json_file_constructor
  end interface json_file

contains

  subroutine initialize(me,p)  ! subroutine constructor
  class(json_file),intent(inout) :: me
  type(json_value),pointer :: p
  me%p => p
  end subroutine initialize

  function json_file_constructor(p) result(me)  ! function constructor
  type(json_value),pointer :: p
  type(json_file) :: me
  me%p => p
  end function json_file_constructor

  subroutine finalize_json_file(me) ! destructor
  type(json_file),intent(inout) :: me
  if (associated(me%p)) then
    write(*,'(A40,I20,I20)') 'finalize_json_file: destroy p', loc(me), loc(me%p)
    deallocate(me%p)
    nullify(me%p)
  else
    write(*,'(A40,I20,I20)') 'finalize_json_file: nothing to destroy', loc(me)
  end if
  end subroutine finalize_json_file

  subroutine test_1() ! test subroutine constructor
  type(json_value),pointer :: p
  type(json_file) :: f
  write(*,*) '... test 1 ...'
  allocate(p)
  p%i = 99
  write(*,*) p%i
  call f%initialize(p)
  write(*,*) f%p%i
  end subroutine test_1

  subroutine test_2() ! test function constructor
  type(json_value),pointer :: p
  type(json_file) :: f
  write(*,*) '... test 2 ...'
  allocate(p)
  p%i = 99
  write(*,*) p%i
  f = json_file(p)
  write(*,*) f%p%i
  end subroutine test_2

end module test_module
!********************************

!********************************
program main
  use test_module
  implicit none
  call test_1()
  call test_2()
end program main
!********************************

The result is:

 ... test 1 ...
          99
          99
           finalize_json_file: destroy p     140732774252832     140342607228384
 ... test 2 ...
          99
  finalize_json_file: nothing to destroy     140732774252856
           finalize_json_file: destroy p     140732774252872     140342607228384
          99
           finalize_json_file: destroy p     140732774252856     140342607228384
finalizer(49100,0x111a8d5c0) malloc: *** error for object 0x7fa40f402dd0: pointer being freed was not allocated
finalizer(49100,0x111a8d5c0) malloc: *** set a breakpoint in malloc_error_break to debug
Abort trap: 6

I'm trying to use a function constructor (test_2) to cast a pointer into a derived type. Note that this type includes a finalizer that destroys the pointer it contains. The subroutine constructor (test_1) works as I expect. However, the function constructor seems to be calling the finalizer during the assignment and destroying the pointer which leaves a dangling pointer that causes an error when the finalizer is called. 

Note that gfortran doesn't do this, and both tests behave the same and work fine. 

Bug, or correct behavior for finalizers? If it's expected, can pointers not be used as arguments for function constructors to types that have finalizers?

0 Kudos
8 Replies
IanH
Honored Contributor II
1,083 Views

The function result should be finalized immediately after the assignment is executed, the local variable f should be finalized when the subroutine completes. The provided output suggests these things are happening.

The program logic seems flawed to me.  Use of pointer components for anything other than simple reference semantics requires things like defined assignment. I think you want assignment to do some sort of transfer of ownership semantics?

Pointer components can be used as function arguments for functions that return objects with finalization, as a simple starrement of fact, but there might be other things you need to do to achieve what you want. Perhaps elaborate on that.

0 Kudos
FortranFan
Honored Contributor II
1,083 Views

Jacob Williams wrote:

..  However, the function constructor seems to be calling the finalizer during the assignment and destroying the pointer which leaves a dangling pointer that causes an error when the finalizer is called. 

Note that gfortran doesn't do this, and both tests behave the same and work fine. 

Bug, or correct behavior for finalizers? If it's expected, can pointers not be used as arguments for function constructors to types that have finalizers?

My impression too is Intel Fortran conforms to the current Fortran 2018 standard as to "when finalization occurs".  The previous 2 standard revisions of 2003 and 2008 had some issues with finalization but which got "cleaned up" in 2018.

Also, gfortran has some known issues with finalization and it is not conformant with the current standard from what I have seen.

Re: "can pointers not be used as arguments for function constructors to types that have finalizers?", as suggested by IanH, you will need to implement what you want to achieve.  Note if assignment instructions are what are of interest, paragraph 1 of section 7.5.6.3 on "When finalization occurs" starts with "When an intrinsic assignment statement is executed  .. .": this then directs you to IanH's point about "definied assignment" 

0 Kudos
FortranFan
Honored Contributor II
1,083 Views

IanH (Blackbelt) wrote:

.. The program logic seems flawed to me.  Use of pointer components for anything other than simple reference semantics requires things ..

Pointer components can be used as function arguments for functions that return objects with finalization, as a simple starrement of fact, but there might be other things you need to do to achieve what you want. Perhaps elaborate on that.

Agree, OP doesn't quite elaborate what is of interest.

If OP can focus on "simple reference semantics" alluded to by IanH, I believe something like the following can be a safer option to adopt for Fortranners who typically want to focus on scientific and technical computing rather than the minefields of dangling pointers and leaked memory:

  • the component of the derived type with the POINTER attribute is *only* employed to point to (valid) targets and thus the finalization is made a simple nullification,
  • the dummy arguments with the POINTER attribute are also given "INTENT(IN)" attribute,
  • consequently the effective argument can be either a valid target or an object with POINTER attribute,
  • and essentially avoid objects of POINTER attribute in code that consumes one's 'classes' e.g., 'json_file' above
!********************************
module test_module

   implicit none

   type :: json_value
      integer :: i = 0
   end type json_value

   type :: json_file
      type(json_value),pointer :: p => null()
      character(len=:), allocatable :: id
   contains
      procedure :: initialize
      final :: finalize_json_file
   end type json_file

   interface json_file
      module procedure :: json_file_constructor
   end interface json_file

contains

   subroutine initialize(me,p)  ! subroutine constructor
      class(json_file),intent(inout) :: me
      type(json_value), pointer, intent(in) :: p !<-- Note 'intent(in)'
      me%p => p
   end subroutine initialize

   function json_file_constructor(p) result(me)  ! function constructor
      type(json_value), pointer, intent(in) :: p !<-- Note 'intent(in)'
      type(json_file) :: me
      me%p => p
      me%id = "function result variable of json_file_constructor"
   end function json_file_constructor

   subroutine finalize_json_file(me) ! destructor
      type(json_file),intent(inout) :: me
      print *, "finalizing ", trim(me%id)
      me%p => null()
      if ( allocated(me%id) ) then
         deallocate(me%id)
      end if
   end subroutine finalize_json_file

   subroutine test_1() ! test subroutine constructor
      type(json_value), target :: p
      type(json_file) :: f
      write(*,*) '... test 1 ...'
      p%i = 99
      write(*,*) p%i
      f%id = "test_1: local object f"
      call f%initialize(p)
      write(*,*) f%p%i
   end subroutine test_1

   subroutine test_2() ! test function constructor
      type(json_value), target :: p
      type(json_file) :: f
      write(*,*) '... test 2 ...'
      p%i = 99
      write(*,*) p%i
      f%id = "test_1: initial object f"
      f = json_file(p)
      f%id = "test_1: object f following 'f = json_file(p)' assignment"
      write(*,*) f%p%i
   end subroutine test_2

end module test_module
!********************************

!********************************
program main
   use test_module
   implicit none
   call test_1()
   call test_2()
end program main
!********************************

 

0 Kudos
FortranFan
Honored Contributor II
1,083 Views

To add to Quote #4, callers of 'classes' such as json_file can work with objects of POINTER attribute also as shown below, except that the program logic becomes "whoever allocates does the clean up" unlike that in the original post where allocation of 'p' is done by the caller but the finalization of its (anonymous) target is attempted via the 'json_file' class which is a recipe for trouble.

   subroutine test_2() ! test function constructor
      type(json_value), pointer :: p
      type(json_file) :: f
      write(*,*) '... test 2 ...'
      allocate(p)
      p%i = 99
      write(*,*) p%i
      f%id = "test_1: initial object f"
      f = json_file(p)
      f%id = "test_1: object f following 'f = json_file(p)' assignment"
      write(*,*) f%p%i
      if ( associated(p) ) then
         deallocate(p)
         p => null()
      end if
   end subroutine test_2

The program output with the case in Quote #4 and this one is expected to be:

 ... test 1 ...
 99
 99
 finalizing test_1: local object f
 ... test 2 ...
 99
 finalizing test_1: initial object f
 finalizing function result variable of json_file_constructor
 99
 finalizing test_1: object f following 'f = json_file(p)' assignment

 

0 Kudos
Jacob_Williams
New Contributor I
1,083 Views

This example is based on a use case from my JSON-Fortran library. The basic idea is that for most users, the higher-level json_file class is used (that includes a set of methods for reading/writing JSON files). Internally, it contains a json_value linked list. However, there are some situations where an expert user may want to manually create or manipulate the json_value linked list, and then put it back into a json_file class. Depending on what you are doing, you may want to then keep this pointer around, or just nullify it. For this use case, we provided this json_file function constructor. 

Originally, because of compiler bugs, json_file did not have a finalizer, so you had to manually call a destroy method when you were done with it, which was not ideal. Now, I want to add a finalizer. The finalizer should destroy the linked list contained within. However, when I add the finalizer, this use case breaks for the reasons shown in the original post. 

I want the function constructor to behave the same as it did before (just take the input pointer and point to it).

I was toying around with this idea (adding an assignment operator and a logical flag to disable finalization for the RHS of the assignment) like so:

!********************************
module test_module

  implicit none

  type :: json_value
    integer :: i = 0
  end type json_value

  type :: json_file
    type(json_value),pointer :: p => null()
    logical :: finalize = .true.
    contains
    procedure,private :: assign_json_file
    generic,public :: assignment(=) => assign_json_file
    procedure :: initialize
    final :: finalize_json_file
  end type json_file

  interface json_file
    module procedure :: json_file_constructor
  end interface json_file

contains

  subroutine assign_json_file(me,f)
  class(json_file),intent(out) :: me
  type(json_file),intent(in)   :: f
  me%p => f%p
  me%finalize = .true.
  end subroutine assign_json_file

  subroutine initialize(me,p)  ! subroutine constructor
  class(json_file),intent(inout) :: me
  type(json_value),pointer :: p
  me%p => p
  end subroutine initialize

  function json_file_constructor(p) result(me)  ! function constructor
  type(json_value),pointer :: p
  type(json_file) :: me
  me%p => p
  me%finalize = .false.  ! don't destroy it
  end function json_file_constructor

  subroutine finalize_json_file(me) ! destructor
  type(json_file),intent(inout) :: me
  if (me%finalize) then
    if (associated(me%p)) then
      write(*,'(A40,I20,I20)') 'finalize_json_file: destroy p', loc(me), loc(me%p)
      deallocate(me%p)
      nullify(me%p)
    else
      write(*,'(A40,I20,I20)') 'finalize_json_file: nothing to destroy', loc(me)
    end if
  end if
  end subroutine finalize_json_file

  subroutine test_1() ! test subroutine constructor
  type(json_value),pointer :: p
  type(json_file) :: f
  write(*,*) '... test 1 ...'
  allocate(p)
  p%i = 99
  write(*,*) p%i
  call f%initialize(p)
  write(*,*) f%p%i
  end subroutine test_1

  subroutine test_2() ! test function constructor
  type(json_value),pointer :: p
  type(json_file) :: f
  write(*,*) '... test 2 ...'
  allocate(p)
  write(*,'(A40,I20,I20)') 'allocate(p)', loc(p)
  p%i = 99
  write(*,*) p%i
  f = json_file(p)
  write(*,*) f%p%i
  end subroutine test_2

end module test_module
!********************************

!********************************
program main
  use test_module
  implicit none
  write(*,*) ''
  call test_1()
  write(*,*) ''
  call test_2()
  write(*,*) ''
end program main
!********************************

The result it:

 
 ... test 1 ...
          99
          99
           finalize_json_file: destroy p     140732783931600     140682035473888
 
 ... test 2 ...
                             allocate(p)     140682035473888
          99
  finalize_json_file: nothing to destroy     140732783931648
          99
           finalize_json_file: destroy p     140732783931648     140682035473888

Which seems to do what I want... However, I maybe need to think about this. Is it safe to disable finalization for all calls to the function constructor? I think so since the only use for that in my case is for an assignment. 

 

0 Kudos
IanH
Honored Contributor II
1,083 Views

Consider the case where you have constructed an object `a` of type json_file using your subroutine, and then you assign object `a` to another object of type json_file `b`. What do you want to happen when `a` and `b` go out of scope and are finalized?

What does asssignment mean for objects of type json_file?

0 Kudos
Jacob_Williams
New Contributor I
1,083 Views

Hmmm...good point. Maybe I should replace the pointer assignment in assign_json_file with a deep copy? That would mean f = json_file(p) is also a deep copy. So, maybe remove the finalize = .false. hack in json_file_constructor and allow p to be destroyed.

Something like this:

!********************************
module test_module

  implicit none

  type :: json_value
    integer :: i = 0
  end type json_value

  type :: json_file
    type(json_value),pointer :: p => null()
    logical :: finalize = .true.
    contains
    procedure,private :: assign_json_file
    generic,public :: assignment(=) => assign_json_file
    procedure :: initialize
    final :: finalize_json_file
  end type json_file

  interface json_file
    module procedure :: json_file_constructor
  end interface json_file

contains

  ! subroutine assign_json_file(me,f)   ! pointer version
  ! class(json_file),intent(out) :: me
  ! type(json_file),intent(in)   :: f
  ! me%p => f%p
  ! me%finalize = .true.
  ! end subroutine assign_json_file

  subroutine assign_json_file(me,f)   ! deep copy version
    class(json_file),intent(out) :: me
    type(json_file),intent(in)   :: f
    type(json_value),pointer :: p
    allocate(p)
    p = f%p
    me%p => p
    write(*,*) 'copied', loc(f%p), 'to', loc(me%p)
    me%finalize = .true.
  end subroutine assign_json_file

  subroutine initialize(me,p)  ! subroutine constructor
  class(json_file),intent(inout) :: me
  type(json_value),pointer :: p
  me%p => p
  end subroutine initialize

  function json_file_constructor(p) result(me)  ! function constructor
  type(json_value),pointer :: p
  type(json_file) :: me
  me%p => p
  !me%finalize = .false.  ! don't destroy it   -- pointer version of = routine
  me%finalize = .true.  ! don't destroy it   -- deep copy version of = routine
  nullify(p) ! probably should do this since p
             ! would be a dangling pointer
             ! when me goes out of scope
  end function json_file_constructor

  subroutine finalize_json_file(me) ! destructor
  type(json_file),intent(inout) :: me
  if (me%finalize) then
    if (associated(me%p)) then
      write(*,'(A40,I20,I20)') 'finalize_json_file: destroy p', loc(me), loc(me%p)
      deallocate(me%p)
      nullify(me%p)
    else
      !write(*,'(A40,I20,I20)') 'finalize_json_file: nothing to destroy', loc(me)
    end if
  end if
  end subroutine finalize_json_file

  subroutine test_1() ! test subroutine constructor
  type(json_value),pointer :: p
  type(json_file) :: f
  write(*,*) '... test 1 ...'
  allocate(p)
  p%i = 99
  write(*,*) p%i
  call f%initialize(p)
  write(*,*) f%p%i
  end subroutine test_1

  subroutine test_2() ! test function constructor
  type(json_value),pointer :: p
  type(json_file) :: f
  write(*,*) '... test 2 ...'
  allocate(p)
  write(*,'(A40,I20,I20)') 'allocate(p)', loc(p)
  p%i = 99
  write(*,*) p%i
  f = json_file(p)
  write(*,*) 'associated(p)', associated(p) ! note that the constructor nullifies p
  write(*,*) f%p%i
  end subroutine test_2

end module test_module
!********************************

!********************************
program main
  use test_module
  implicit none
  !write(*,*) ''
  !call test_1()
  write(*,*) ''
  call test_2()
  write(*,*) ''
end program main
!********************************

Results:

 ... test 2 ...
                             allocate(p)     140194349056352
          99
 copied       140194349056352 to       140194349056416
           finalize_json_file: destroy p     140732703875328     140194349056352
 associated(p) F
          99
           finalize_json_file: destroy p     140732703875280     140194349056416

The user would just need to understand that if they use the function constructor, it will nullify the pointer.

This is making me think the function constructor is not a good solution for this use case when there is a finalizer, and the subroutine one is better. We shouldn't have to do a deep copy just to get a pointer into the class.

0 Kudos
IanH
Honored Contributor II
1,083 Views

Do you want a deep copy? Do you want shared reference semantics? It's up to you.

An example of how you can use reference counting to implement shared references attached. Apologies for any head compiling errors.

0 Kudos
Reply