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

Memory leak in fortran 2003

Bertalot__Federico
708 Views

I have a memory leak when using a "constructor"(which is just a static function) to create an initialize a derived type object.

I have two subroutines that seem to be equivalent, but one of them has a memory leak (mult_leak), while the other hasn't (mult_noleak).

I don't understand which is the difference.

 

program main
    use lala
    type(mytype) :: mt1, mt2, mt3
    integer :: i
    real, allocatable, dimension(:,:) :: dat
    allocate(dat(1000, 1000))
    dat = 1.5

    do i=1,10000000
        mt1 = creador(dat)
        mt2 = creador(dat)
        mt3 = mult_leak(mt1, mt2)
        if(modulo(i,1000)==0) then
            print*, i, mt3%dat(1,1)
        endif       
    end do

end program
module lala

    type mytype

        integer :: nx, ny
        real, allocatable, dimension(:,:) :: dat

        contains
            private
            procedure :: init
    end type

interface creador
    procedure p_creador
end interface

contains
    subroutine init(this, dat)
        class(mytype) :: this
        real, allocatable, dimension(:,:) :: dat
        integer, dimension(2) :: s
        s = shape(dat)
        this%nx = s(1)
        this%ny = s(2)

        allocate(this%dat, source=dat)
    end subroutine

    function p_creador(dat) result(res)
        type(mytype), allocatable :: res
        real, allocatable, dimension(:,:) :: dat

        allocate(res)
        call res%init(dat)
    end function

    function mult_noleak(cf1, cf2) result(cfres)
        class(mytype), intent(in) :: cf1, cf2
        class(mytype), allocatable :: cfres

        real, dimension(:,:), allocatable :: aux

        allocate(cfres)

        aux=cf1%dat * cf2%dat

        call cfres%init(aux)

    end function

    function mult_leak(cf1, cf2) result(cfres)
        class(mytype), intent(in) :: cf1, cf2
        class(mytype), allocatable :: cfres

        real, dimension(:,:), allocatable :: aux

        aux=cf1%dat * cf2%dat
        cfres = creador(aux)

    end function
end module

 

0 Kudos
7 Replies
FortranFan
Honored Contributor II
708 Views

See this thread, especially the last quote (#4) by Dr Fortran: https://software.intel.com/pt-br/node/814205

Which version of Intel Fortran compiler was used in your test?  In case it's earlier than 19.0, are you able to try with a recent one, say 19.0 Update 2, and recheck?  Also, how about a test using a somewhat modified version of your code where the Fortran 2008 facility of BLOCK construct is used to ensure the objects are finalized in order for your memory leak tool to not report any false positives in terms of leaks?

module lala

   type mytype

      integer :: nx, ny
      real, allocatable, dimension(:,:) :: dat

   contains
      private
      procedure :: init
   end type

   interface creador
      procedure p_creador
   end interface

contains

   subroutine init(this, dat)
      class(mytype), intent(inout) :: this      !<-- editorial suggestion: use intent
      real, intent(in), allocatable :: dat(:,:) !
      integer, dimension(2) :: s
      s = shape(dat)
      this%nx = s(1)
      this%ny = s(2)

      allocate(this%dat, source=dat)
   end subroutine

   function p_creador(dat) result(res)
      type(mytype), allocatable :: res
      real, intent(in), allocatable :: dat(:,:) !<-- editorial suggestion: use intent

      allocate(res)
      call res%init(dat)
   end function

   function mult_noleak(cf1, cf2) result(cfres)
      class(mytype), intent(in) :: cf1, cf2
      class(mytype), allocatable :: cfres

      real, dimension(:,:), allocatable :: aux

      allocate(cfres)

      aux=cf1%dat * cf2%dat

      call cfres%init(aux)

   end function

   function mult_leak(cf1, cf2) result(cfres)
      class(mytype), intent(in) :: cf1, cf2
      class(mytype), allocatable :: cfres

      real, dimension(:,:), allocatable :: aux

      aux=cf1%dat * cf2%dat
      cfres = creador(aux)

   end function
end module
program main

   block
      use lala, only : mytype, creador, mult_noleak
      type(mytype) :: mt1, mt2, mt3
      integer :: i
      integer, parameter :: DAT_SIZE = 1 !<-- this size can be varied in different trials
      real, allocatable, dimension(:,:) :: dat
      allocate(dat(DAT_SIZE, DAT_SIZE))
      dat = 1.5

      do i = 1, DAT_SIZE*DAT_SIZE
         mt1 = creador(dat)
         mt2 = creador(dat)
         mt3 = mult_noleak(mt1, mt2)
         if(modulo(i,DAT_SIZE)==0) then
            print*, i, mt3%dat(1,1)
         endif
      end do
   end block

end program

Edit: the link to the thread mentioned in the first line that missing in my first attempt has been added.

0 Kudos
gib
New Contributor II
708 Views

Something missing:

"See this thread, especially the last quote (#4) by Dr Fortran."

0 Kudos
FortranFan
Honored Contributor II
708 Views

gib wrote:

Something missing:

"See this thread, especially the last quote (#4) by Dr Fortran."

Oops!  The link has been added.

0 Kudos
Steve_Lionel
Honored Contributor III
708 Views

I don't think the link applies - there are no finalizers in this program. I tried it with 19.0.4 and found no leak.

0 Kudos
FortranFan
Honored Contributor II
708 Views

Steve Lionel (Ret.) (Blackbelt) wrote:

I don't think the link applies - there are no finalizers in this program. I tried it with 19.0.4 and found no leak.

@Bertelot, Frederico,

Sorry I should have been clearer: I was only trying to help, but was in a hurry yesterday with a deadline while working from a server with restricted access and missing a set of tools to analyze.  What I was trying to suggest is

  1. Be wary of false positives as well as false negatives with memory leaks in your checks,
  2. As part of point 1 with Fortran code, try to be consistent in your checks with the Fortran standard on a "finalizable type" and finalization only because we've noticed some parallels with those rules and what Intel Fortran compiler generally does with user code even if a 'finalizable type' is not involved such as with your derived type.  This is only why I suggested what I did in Quote #2. 
  3. If you can, please do submit support request with Intel at their support center: https://supporttickets.intel.com/servicecenter?lang=en-US and reference Quote #2 as well as this comment.

Do note I could reproduce your issue with Intel Fortran compiler 19.0 Update 2 yesterday though with a proprietary memory leak analyzer.  But I had made a change to your main program ONLY by reducing the problem size to keep within the available system resources as follows:

program main
    use lala
    type(mytype) :: mt1, mt2, mt3
    integer :: i
    real, allocatable, dimension(:,:) :: dat
    integer, parameter :: DAT_SIZE = 1
    allocate(dat(DAT_SIZE, DAT_SIZE))
    dat = 1.5

    do i=1, DAT_SIZE*DAT_SIZE
        mt1 = creador(dat)
        mt2 = creador(dat)
        mt3 = mult_leak(mt1, mt2)
        if(modulo(i, DAT_SIZE)==0) then
            print*, i, mt3%dat(1,1)
        endif       
    end do

end program

And now with this code and Intel Fortran 19.0 compiler and Update 4 as well as Intel Analyzer 2019, the memory leak can be noticed which is contrary to the comment in Quote #5:

mlk.PNG

0 Kudos
Bertalot__Federico
708 Views

Hello.

First of all i've detected the leak in three ways:

1) The memory usage explodes after some iterations.

2) i noticed that the memory usage increases in each iteration, using 'malloc_stats' in gdb.

3) using valgrind.

 

having said this, i think i have found the problem. The 'mult_leak' function result is a polymorphic allocatable object (class(mytype), allocatable) which has an allocatable component (dat). this is completely unnecesary. If redefine cfres, the leak disappears.

 

function mult_leak(cf1, cf2) result(cfres)

      class(mytype), intent(in) :: cf1, cf2
      type(mytype), allocatable :: cfres   <----- i changed this definition
      real, dimension(:,:), allocatable :: aux

      aux=cf1%dat * cf2%dat

      cfres = creador(aux)

end function

 

or

 

function mult_leak(cf1, cf2) result(cfres)

      class(mytype), intent(in) :: cf1, cf2
      type(mytype) :: cfres   <----- i changed this definition
      real, dimension(:,:), allocatable :: aux

      aux=cf1%dat * cf2%dat

      cfres = creador(aux)

end function

 

Both solutions works correctly. 

A last question remains, and it is why 'mult_noleak' works fine with the polymorphic result. Maybe because in this subroutine the allocation is explicit?

 

0 Kudos
FortranFan
Honored Contributor II
708 Views

Bertalot, Federico wrote:

.. having said this, i think i have found the problem. The 'mult_leak' function result is a polymorphic allocatable object (class(mytype), allocatable) which has an allocatable component (dat). this is completely unnecesary. If redefine cfres, the leak disappears.

.. 

A last question remains, and it is why 'mult_noleak' works fine with the polymorphic result. Maybe because in this subroutine the allocation is explicit?

I think you are misunderstanding your findings:

  1. Intel's own tool of Intel Inspector 2019 (as well as a proprietary one) with your code in the original post shows memory leaks with both 'mult_noleak' and 'mult_leak',
  2. Besides, it should NOT matter whether the function result is polymorphic when it comes to memory leaks.  And Intel Inspector shows leaks in both cases e.g., when your 'mult_noleak' function has a return type of TYPE(mytype) and CLASS(mytype).

I think you should follow-up with Intel Support on this issue.

0 Kudos
Reply