GSoC: Linked List || Blog post by Chetan Karwa || #3

cc: @Arjen , @milancurcic

@Chetan_Karwa ,

Re: my earlier comment that you may be studying, attached please find a smaller example you can review. Note the lines 24 and 67 which are currently commented out. You can try this example with and without those lines commented and analyze the program using Valgrind / Intel Inspector, etc. and evaluate the impact on memory leaks. Also, note the 2 BLOCK constructs in the driver program, the first tries to mimic what you may be doing whereas the second a typical consumer might do. You can try to look at the Fortran semantics and the memory leak effect based on how a derived type container might be constructed with and without finalizers.

A simple example of a "container" derived type with components of POINTER attribute

Fortran module with a driver program

module node_m
   type :: node_t
      class(*), allocatable :: dat
   contains
      procedure, pass(this) :: destroy
   end type
contains
   subroutine destroy( this )
      class(node_t), intent(inout) :: this
      print *, "In node_m::destroy"
      if ( allocated(this%dat) ) then
         deallocate( this%dat )
      end if
      return
   end subroutine
end module

module list_m
   use node_m, only : node_t
   type :: list_t
      character(len=50) :: lname = "Default"
      type(node_t), pointer :: tail => null()
   contains
      !final :: finalize_list_t
      procedure, pass(this) :: append => append_tail
      procedure, pass(this) :: destroy
   end type
contains
   subroutine append_tail( this, dat )
      class(list_t), intent(inout) :: this
      class(*), intent(in)         :: dat
      ! Checks elided
      allocate( this%tail )
      allocate( this%tail%dat, source=dat )
   end subroutine
   subroutine destroy( this )
      class(list_t), intent(inout) :: this
      if ( associated(this%tail) ) then
         call this%tail%destroy()
         deallocate( this%tail )
      end if
      this%tail => null()
      return
   end subroutine
   subroutine finalize_list_t( this )
      type(list_t), intent(inout) :: this
      print *, "Finalizing list_t object with name: ", "'", trim(this%lname), "'"
      call destroy( this )
      return
   end subroutine
end module

module node_with_list_m
   use list_m, only : list_t
   type :: node_with_list_t
      type(list_t), allocatable :: list
   end type
end module

module list_of_lists_m
   use list_m, only : list_t
   use node_with_list_m, only : node_with_list_t
   type :: list_of_lists_t
      character(len=50) :: lname = "Default"
      type(node_with_list_t), pointer :: tail => null()
   contains
      !final :: finalize_list_of_lists_t
      procedure, pass(this) :: append => append_tail
      procedure, pass(this) :: destroy
   end type
contains
   function create_node( list ) result(node)
      type(list_t), intent(in) :: list
      type(node_with_list_t) :: node
      allocate( node%list, source=list )
      node%list%lname = "create_node function result"
   end function
   subroutine append_tail( this, dat )
      class(list_of_lists_t), intent(inout) :: this
      class(*), intent(in)                  :: dat
      ! Local variables
      type(list_t) :: list
      list%lname = "local object 'list' in append_tail method"
      call list%append( dat )
      allocate( this%tail, source=create_node(list) )
      this%tail%list%lname = "added item via append_tail method"
   end subroutine
   subroutine destroy( this )
      class(list_of_lists_t), intent(inout) :: this
      if ( associated(this%tail) ) then
         deallocate( this%tail )
      end if
      this%tail => null()
      return
   end subroutine
   subroutine finalize_list_of_lists_t( this )
      type(list_of_lists_t), intent(inout) :: this
      print *, "Finalizing list_of_lists_t object with name: ", "'", trim(this%lname), "'"
      call destroy( this )
      return
   end subroutine
end module

   ! Driver program to check memory leak
   use list_of_lists_m, only : list_of_lists_t

   blk1: block
      type(list_of_lists_t) :: foo
      foo%lname = "foo"
      call foo%append( 42 )
      print *, "'foo' appended with an integer item."
      call foo%destroy()
   end block blk1

   blk2: block
      type(list_of_lists_t) :: bar
      bar%lname = "bar"
      call bar%append( 42 )
      print *, "'bar' appended with an integer item."
   end block blk2

end

Hope this will be of some help to you.

Best,

1 Like