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

memory leak with move_alloc

riad_h_1
Beginner
1,067 Views

Dear all,

I am using "move_alloc" to transfer the allocation from an intrinsic array to an allocatable member of a DT and I get a memory growth issue (ifort 19 for Mac OS)
Here is a sample:

! compiled with: ifort leak_movealloc.f90 -o leak_movealloc
! (ifort version: 19.0.5 for Mac OS)

PROGRAM leak_movealloc
implicit none

type :: i_t
   integer, allocatable :: v(:,:)
end type i_t

integer, parameter   :: n = 2000, m = 300, RepeateNtimes = 100
type(i_t)            :: a
integer              :: it, Imat0(n,m) = 0
integer, allocatable :: Imat(:,:)

do it = 1, RepeateNtimes

   allocate(Imat, source = Imat0)
!
!- Move allocation from Imat to a%v:
!
   call iMoveAlloc ( from = Imat, to = a )  ! <-- This produces a memory growth
   
  !call move_alloc ( from = Imat, to = a%v ) ! <-- But not this!
   
   write(*,'(a)',advance='no') "hit return to continue" ; read*
   
end do

CONTAINS

   SUBROUTINE iMoveAlloc ( from, to )
   integer  , allocatable, intent(in out) :: from(:,:)
   type(i_t),              intent(   out) :: to

   call move_alloc (from = from, to = to%v)
   
   END SUBROUTINE iMoveAlloc
   
END PROGRAM leak_movealloc

The problem occurs when move_alloc is not called directly but from the subroutine iMoveAlloc (in which the argument "to" has intent "out" though)

The problem goes away if I deallocate "a%v" before calling iMoveAlloc. 

Does anyone have any idea what the problem is?

Best regards,

Riad

0 Kudos
1 Solution
Ferdinand_T_
New Contributor II
1,067 Views

Hi riad h., these kinds of memory-leaks have troubled me for a long time with ifort, even though your issue is new since version 18 (linux version). As a workaround, I got used to writing finalizers, e.g. as follows

type :: i_t
    integer, allocatable :: v(:,:)
contains
    final :: i_t_final
end type i_t

! [...]

subroutine i_t_final(this)
    type(i_t), intent(inout) :: this
    if (allocated(this%v)) deallocate(this%v)
end subroutine

These finalizers can eventually be removed once the issues are fixed by Intel.

Kind regards
Ferdinand

View solution in original post

0 Kudos
9 Replies
jimdempseyatthecove
Honored Contributor III
1,067 Views

In subroutine iMovAlloc, dummy "to" is actual argument "a" from caller. The caller's "a" is not being replaced (its member variable "v" is). Thus I think the issue is the intent attribute of iMoveAlloc "to" may need to be "in".

Note, in your alternate call using a%v (and using to=to in iMoveAlloc) then intent(out) is appropriate.

Jim Dempsey

0 Kudos
riad_h_1
Beginner
1,067 Views

Hi Jim and thanks for your answer.

I'm not sure I understand. For a dummy argument with intent(out), components are initialised to its default values (if any, otherwise become undefined) and allocatable members are deallocated on entry to the subroutine. Thus, here, iMovAlloc, deallocates just a%v. 

And consider I replace iMoveAlloc by (but of course, that's not what I want to do):

   SUBROUTINE copyThenDealloc ( from, to )
   integer  , allocatable, intent(in out) :: from(:,:)
   type(i_t),              intent(   out) :: to

   allocate(to%v, source = from)
   deallocate(from)
   
   END SUBROUTINE copyThenDealloc

No leak is produced. 

Riad

0 Kudos
jimdempseyatthecove
Honored Contributor III
1,066 Views

In #3

The UDT variable to is declared with intent(out)
the variable to is not being redefined, rather a member variable (v) within it is being allocated then initialized.
In a general sense, UDT variable to could contain additional member variables, would you intend for these to be destroyed and redefined with default values (should you have a i_t initializer)?

The observation that the code works is by no means an assurance that the code is correct (and won't fail under different circumstances).

Jim Dempsey

0 Kudos
riad_h_1
Beginner
1,066 Views

yes in my real code, the DT contains additional members (with default values). And yes, in that case, they are also (re)initialised in iMoveAlloc. 

It seemed to me by using "out" I didn't have to worry about destroying the members of "to" and that they would be automatically destroyed on entry (deallocated for allocatable members, initialised to default values for others).

Declaring "to" with intent(inout), requires more work. With my second routine (copyThenDealloc), for example, I should first test if to%v is allocated (and if so, deallocate it), etc.

Riad

0 Kudos
Ferdinand_T_
New Contributor II
1,068 Views

Hi riad h., these kinds of memory-leaks have troubled me for a long time with ifort, even though your issue is new since version 18 (linux version). As a workaround, I got used to writing finalizers, e.g. as follows

type :: i_t
    integer, allocatable :: v(:,:)
contains
    final :: i_t_final
end type i_t

! [...]

subroutine i_t_final(this)
    type(i_t), intent(inout) :: this
    if (allocated(this%v)) deallocate(this%v)
end subroutine

These finalizers can eventually be removed once the issues are fixed by Intel.

Kind regards
Ferdinand

0 Kudos
riad_h_1
Beginner
1,066 Views

Hi Ferdinand,

Oh yes, that works!

In general, I use finalizers only for DT containing pointers, I wouldn't have thought it would be necessary for allocatable components.

Many thanks. 

Riad.

0 Kudos
FortranFan
Honored Contributor II
1,066 Views

riad h. wrote:

.. I am using "move_alloc" to transfer the allocation from an intrinsic array to an allocatable member of a DT and I get a memory growth issue (ifort 19 for Mac OS) ..

@riad h.,

My impression is Intel Fortran team can notice the issue with your example as well as a further simplified one using Intel's own tools in Parallel Studio such as Intel Inspector.  The issue can also be confirmed with a private memory analyzer I use.  Note the same simple code when analyzed based on compilation output from another processor e.g., gfortran does NOT show a leak, so I'm inclined to believe this is an issue with Intel Fortran compiler.  I believe your code is conforming.

If you are able to, you should consider submitting a support request at Intel OSC center: https://supporttickets.intel.com/servicecenter?lang=en-US

   type :: t
      integer, allocatable :: i
   end type
   integer, allocatable :: n
   type(t) :: foo
   n = 42
   call my_move_alloc( n, foo )
   print *, "foo%i = ", foo%i, "; expected is 42"
contains
   subroutine my_move_alloc( from, to )
      integer, allocatable, intent(inout) :: from
      type(t), intent(out)                :: to
      call move_alloc( from, to%i )
   end subroutine
end

leak.PNG

0 Kudos
riad_h_1
Beginner
1,066 Views

@FortranFan,

I'll take your advice and Thanks for your example and comment.

 

0 Kudos
Devorah_H_Intel
Moderator
1,066 Views

Thank you for your report - this case has been escalated to compiler engineering.

0 Kudos
Reply