I'm trying to create a linked list structure in Fortran for a fixed point iteration between particles in a computational zone. Particles are iteratively traced through a computational zone, their properties from each step are stored; and they interact with the particle properties from the previous iteration.
For this problem I have two linked lists, one which holds the particle properties from the previous iteration (list_use
, with which the particles currently being traced through the domain interact) and another list which accumulates the properties of the particles as they are traced through the computational zone. After one iteration (i.e. after all particles have been traced through the domain once), I want to discard list_use
(interactions with this data have already been computed), copy list_buildup
into list_use
and then discard list_buildup
, so that it can be repopulated with the next data from the iteration.
I appear to have a memory leak when copying and discarding the lists. Here's a reduced bit of code which replicates the memory leak. As far as I can tell, the leak occurs in updateASR
. I would expect the process memory before this subroutine to be equal to the memory after it, but using the diagnostics on VisualStudio, it shows the memory increasing every time that updateASR
is called, eventually leading to the program terminating (with an access violation error). Here's an image showing the VS process memory diagnostic. I guess that destroyASREntries
is somehow not doing what I actually want it to do?
I'm not very experienced with pointers in Fortran and therefore a bit stuck, so any help would be really appreciated!
module linked_list
!---------------------------------------------------------------------------------
! Type containing the data for an ASR entry, used to compute interactions between rays.
type ASR_entry
real :: intensity !<- The intensity of the ASR entry
real :: ang_freq !<- Angular frequency
real,dimension(3) :: wavevector !<- Wavevector (x,y,z): Cartesian.
end type ASR_entry
!---------------------------------------------------------------------------------
! A node type in the linked list for the ASR.
type ASR_Node
type(ASR_Node),pointer :: next => null()
type(ASR_Node),pointer :: prev => null()
type(ASR_entry) :: node_entry
end type ASR_Node
!---------------------------------------------------------------------------------
! For interaction, each cell contains one of these ASR linked lists, which itself contains the nodes, which contain the entry.
type ASR_cell_ll
type(ASR_Node),pointer :: head => null() !<- first%next points to first node
type(ASR_Node),pointer :: last => null() !<- last%prev points to last node
integer(kind=4) :: size = 0 !<- Number of ASR entries in the linked list
end type ASR_cell_ll
contains
!---------------------------------------------------------------------------------
! Create the ASR linked list in every cell.
subroutine createASRcell(list)
implicit none
type(ASR_cell_ll), pointer :: list
if(associated(list)) call Abort("Must pass null pointer of type 'ASR_cell_ll' to createASRcell.")
!- Allocate memory - is this necessary??
allocate(list)
allocate(list%head,list%last)
list%head%next => list%last !<- If list is empty, then the first entry points to the last entry which is null
list%last%prev => list%head
list%size = 0
end subroutine createASRcell
!---------------------------------------------------------------------------------
! Delete all ASR entries
subroutine destroyASREntries(list)
implicit none
type(ASR_cell_ll), pointer :: list
type(ASR_Node), pointer :: dCurrent=>null(), dNext=>null()
if (.not. associated(list)) return
allocate(dCurrent,dNext)
dCurrent => list%head
dNext => dCurrent%next
!- Deallocate all data nodes in list
do
nullify(dCurrent%prev) !- Remove dangling pointers from the list structure.
deallocate(dCurrent)
if (.not. associated(dNext)) exit
dCurrent => dNext
dNext => dCurrent%next
end do
nullify(dCurrent,dNext) !- Remove dangling pointers
list%size=0
deallocate(list)
end subroutine destroyASREntries
!---------------------------------------------------------------------------------
!- This subroutine removes the old entries in list_use, copies the list_buildup entries into list_use, then empties list_buildip for the next iteration.
subroutine updateASR(list_use, list_buildup)
implicit none
type(ASR_cell_ll),pointer :: list_use, list_buildup
!First destroy all entries from the previous ASR iteration, before recreating the list.
call destroyASREntries(list_use)
call createASRcell(list_use)
!Then make the use list the previous iterations buildup list.
list_use => list_buildup
!The stop buildup from pointing to the use list's new entries, before recreating buildup as blank.
nullify(list_buildup)
call createASRcell(list_buildup)
end subroutine updateASR
end module linked_list
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
module definitions
implicit none
integer :: nx,ny,nz,nbeams !Dimensions of the linked list domain.
integer :: ix,iy,iz,ibeam !Loop variables
end module definitions
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
program main
use definitions
use linked_list
implicit none
type(asr_cell_ll),pointer :: list_use,list_buildup !<-The temporary and used linked list.
integer :: i
call createASRcell(list_buildup)
call createASRcell(list_use)
do i=1,1000000000
call updateASR(list_use,list_buildup)
enddo
end program main
I compiled the above with ifort.
CodePudding user response:
First, let's look at createASRcell
. It returns a ASR_cell_ll
with size=0
. So why are you allocating memory? You should only allocate a node when you want a node. I think createASRcell
should be
subroutine createASRcell(list)
type(ASR_cell_ll), pointer :: list
if(associated(list)) call Abort("Must pass null pointer of type 'ASR_cell_ll' to createASRcell.")
list%head => null()
list%last => null()
list%size = 0
end subroutine
Second, let's look at destroyASREntries
. The lines
allocate(dCurrent,dNext)
dCurrent => list%head
dNext => dCurrent%next
are creating two nodes, at dCurrent
and dNext
, and then immediately losing track of these nodes to point dCurrent
and dNext
at new targets. This will leak the memory you just allocated. The allocate
statement just shouldn't be there. There's also quite a lot of excess deallocation going on. Simplifying the subroutine, we get
subroutine destroyASREntries(list)
type(ASR_cell_ll), pointer :: list
type(ASR_Node), pointer :: dCurrent, dNext
if (.not. associated(list)) return
dCurrent => list%head
!- Deallocate all data nodes in list
do while(associated(dCurrent))
dNext => dCurrent%next
nullify(dCurrent%prev)
nullify(dCurrent%next)
deallocate(dCurrent)
dCurrent => dNext
end do
! - Deallocate the list itself
deallocate(list)
end subroutine destroyASREntries
Finally, let's look at updateASR
. I don't quite understand what you're trying to do here, but the subroutine is going to cause problems. The lines
call destroyASREntries(list_use)
call createASRcell(list_use)
list_use => list_buildup
will clean up the old ASR_cell_ll
pointed to by list_use
, create a new empty ASR_cell_ll
, again pointed to by list_use
, and then immediately lose track of this new list by pointing list_use
at list_buildup
. This will leak all the memory of the newly created ASR_cell_ll
.
CodePudding user response:
Thanks to @veryreverie for their answer which helped solve the leak and clear up my misunderstanding. The issue was due to allocating pointers before then repointing them to new memory in createASRcell
and destroyASREntries
. Here is the diagnotic with the new code showing no memory leak. Here is the modified, working code without memory leaks in case anyone is interested:
module linked_list
!---------------------------------------------------------------------------------
! Type containing the data for an ASR entry, used to compute interactions between rays.
type ASR_entry
real :: intensity !<- The intensity of the ASR entry
real :: ang_freq !<- Angular frequency
real,dimension(3) :: wavevector !<- Wavevector (x,y,z): Cartesian.
end type ASR_entry
!---------------------------------------------------------------------------------
! A node type in the linked list for the ASR.
type ASR_Node
type(ASR_Node),pointer :: next => null()
type(ASR_Node),pointer :: prev => null()
type(ASR_entry) :: node_entry
end type ASR_Node
!---------------------------------------------------------------------------------
! For interaction, each cell contains one of these ASR linked lists, which itself contains the nodes, which contain the entry.
type ASR_cell_ll
type(ASR_Node),pointer :: head => null() !<- first%next points to first node
type(ASR_Node),pointer :: last => null() !<- last%prev points to last node
integer(kind=4) :: size = 0 !<- Number of ASR entries in the linked list
end type ASR_cell_ll
contains
!---------------------------------------------------------------------------------
! Create the ASR linked list in every cell.
subroutine createASRcell(list)
implicit none
type(ASR_cell_ll), pointer :: list
if(associated(list)) call Abort("Must pass null pointer of type 'ASR_cell_ll' to createASRcell.")
allocate(list)
allocate(list%head,list%last)
list%head%next => list%last !<- If list is empty, then the first entry points to the last entry which is null
list%last%prev => list%head
list%size = 0
end subroutine createASRcell
!---------------------------------------------------------------------------------
! Delete all ASR entries
subroutine destroyASREntries(list)
implicit none
type(ASR_cell_ll), pointer :: list
type(ASR_Node), pointer :: dCurrent=>null(), dNext=>null()
if (.not. associated(list)) return
dCurrent => list%head
!- Deallocate all data nodes in list
do while(associated(dCurrent))
dNext => dCurrent%next
nullify(dCurrent%prev) !- Remove dangling pointers from the list structure.
nullify(dCurrent%next) !- Remove dangling pointers from the list structure.
deallocate(dCurrent)
dCurrent => dNext
end do
! - Deallocate the list itself
deallocate(list)
end subroutine destroyASREntries
!---------------------------------------------------------------------------------
!- This subroutine removes the old entries in list_use, copies the list_buildup entries into list_use, then empties list_buildip for the next iteration.
subroutine updateASR(list_use, list_buildup)
implicit none
type(ASR_cell_ll),pointer :: list_use, list_buildup
call destroyASREntries(list_use) !First destroy all entries from the previous ASR iteration
list_use => list_buildup !Then make the use list the previous iterations buildup list.
nullify(list_buildup) !The stop buildup from pointing to the use list's new entries
end subroutine updateASR
end module linked_list
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
module definitions
implicit none
integer :: nx,ny,nz,nbeams !Dimensions of the linked list domain.
integer :: ix,iy,iz,ibeam !Loop variables
end module definitions
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
program main
use definitions
use linked_list
implicit none
type(asr_cell_ll),pointer :: list_use=>null(),list_buildup=>null() !<-The temporary and used linked list.
integer :: i
call createASRcell(list_buildup)
call createASRcell(list_use)
do i=1,1000000000
call updateASR(list_use,list_buildup)
enddo
end program main