I'm looking for a way to build a tree structure using a User-Defined Type in Fortran 2008. While I can get some basic code working, I'm encountering memory leaks I am unable to pinpoint.
The tree structure does not have to be overly generic since it's being used as a one-time insert and multiple-read kind of storage, which is why I decided to use allocatables. Since Fortran does not allow to use a type for an allocatable as one of its own members, I am using an intermediate structure referenced by a pointer to store that allocatable. So, the following is what I would like to use, but is not allowed:
type :: invalid_section
type(invalid_section), dimension(:), allocatable :: subsections
end type
In the following example I'm using a lazy allocation (only allocate it when there are child nodes to add/present) of that pointer to the type holding the allocatable.
module sectiontest
type :: section
type(subsections), pointer :: subsections_ => null()
contains
procedure, pass(self) :: section_assign
generic :: assignment(=) => section_assign
final :: section_cleanup, section_cleanup_arr
end type
type :: subsections
type(section), dimension(:), allocatable :: arr
end type
interface section
module procedure constructor
end interface
contains
type(section) function constructor(subsections)
type(section), optional, intent(in) :: subsections(:)
integer :: idx
print *, "constructor"
if (present(subsections)) then
print *, "allocating subsection"
allocate(constructor%subsections_)
allocate(constructor%subsections_%arr(size(subsections)))
do idx=1,size(subsections)
! make sure we recursively copy everything
constructor%subsections_%arr(idx) = subsections(idx)
enddo
endif
end function
recursive subroutine section_assign(self, rhs)
class(section), intent(inout) :: self
type(section), intent(in) :: rhs
integer :: idx
print *, "assign"
if (associated(self%subsections_)) then
deallocate(self%subsections_)
endif
if (associated(rhs%subsections_)) then
print *, "allocation subsection"
allocate(self%subsections_)
allocate(self%subsections_%arr(size(rhs%subsections_%arr)))
do idx=1,size(rhs%subsections_%arr)
self%subsections_%arr(idx) = rhs%subsections_%arr(idx)
enddo
endif
end subroutine
recursive subroutine section_cleanup(sec)
type(section), intent(inout) :: sec
print *, "section_cleanup"
if (associated(sec%subsections_)) then
print *, " deallocated a subsection"
deallocate(sec%subsections_)
endif
end subroutine
recursive subroutine section_cleanup_arr(arr)
type(section), dimension(:), intent(inout) :: arr
integer :: idx
print *, "deallocating array of sections of size:", size(arr)
do idx=1,size(arr)
print *, "deallocating subsection array index", idx
if (associated(arr(idx)%subsections_)) then
print *, " deallocated a subsection"
deallocate(arr(idx)%subsections_)
endif
end do
end subroutine
subroutine demo()
type(section) :: root
root = section(subsections=[ &
section(subsections=[section(), section(), section()]), &
section() &
])
end subroutine
end module sectiontest
program main
use sectiontest
implicit none
call demo()
end program
From gfortran
(7 and 9), flang
and nagfor
I get direct memory leaks originating from allocate(constructor%subsections_)
in the constructor
.
Here from gfortran-7
and built with -fsanitize=address
:
==26536==ERROR: LeakSanitizer: detected memory leaks
Direct leak of 48 byte(s) in 1 object(s) allocated from:
#0 0x7f965539c510 in malloc (/usr/lib64/libasan.so.4+0xdc510)
#1 0x407e35 in __sectiontest_MOD_constructor /users/tiziano/work/tests/fortran/cp2k_input_parser/recursive_mwe.f90:31
#2 0x40432a in __sectiontest_MOD_demo /users/tiziano/work/tests/fortran/cp2k_input_parser/recursive_mwe.f90:92
#3 0x4090d9 in MAIN__ /users/tiziano/work/tests/fortran/cp2k_input_parser/recursive_mwe_prog.f90:5
#4 0x409119 in main /users/tiziano/work/tests/fortran/cp2k_input_parser/recursive_mwe_prog.f90:2
#5 0x7f96543c2f89 in __libc_start_main (/lib64/libc.so.6+0x20f89)
I'm looking for either an alternative implementation (but preferably a similar elegant initialization) or an explanation and possible solution for the memory leak.
Fortran 2008 supports a type containing an allocatable component of the type being defined. This simplifies the code to:
module sectiontest
type :: section
type(section), allocatable :: subsections(:)
end type
contains
subroutine demo()
type(section) :: root
root = section( subsections=[ &
section(subsections=[section(), section(), section()]), &
section() ])
end subroutine
end module sectiontest
program main
use sectiontest
implicit none
call demo()
end program
Recent versions of gfortran support this language feature.
For compilers that do not sufficiently support Fortran 2008, the code in the question is a reasonable work around and will work on compilers that correctly implement Fortran 2003.
However, gfortran (up to 9.1.1 at least) does not correctly implement finalization of function results - hence the observed memory leak.