public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries
@ 2022-08-26  9:37 federico.perini at gmail dot com
  2022-08-30 18:59 ` [Bug fortran/106750] Memory leak calling array slice " anlauf at gcc dot gnu.org
                   ` (3 more replies)
  0 siblings, 4 replies; 5+ messages in thread
From: federico.perini at gmail dot com @ 2022-08-26  9:37 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750

            Bug ID: 106750
           Summary: Memory leak calling section of derived type containing
                    `allocatable` entries
           Product: gcc
           Version: 9.2.0
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
          Assignee: unassigned at gcc dot gnu.org
          Reporter: federico.perini at gmail dot com
  Target Milestone: ---

Running a large CFD program I've found a memory leak gfortran 9.2.0 (sorry:
unable to test other versions on that system) that occurs when: 

- derived type contains `allocatable` entries
- a chunk of an array of the aforementioned derived type is used as input to a
function
- happens whether or not the derived type contains a final routine

Here's a minimal working example: 

module tmod
  implicit none

  type, public :: t
    integer :: i,j,k
    integer, allocatable :: a(:) ! No leaks if these are fixed-size
    integer, allocatable :: b(:) ! No leaks if these are fixed-size
!    integer :: a(3),b(20) ! uncomment to test fixed-size
  end type t

  contains

  integer function do_with_array(ts) result(l)
     type(t), intent(in) :: ts(2)

     integer :: i(2),j(2),k(2)
     i = max(ts(:)%i,0)
     j = max(ts(:)%j,0)
     k = max(ts(:)%k,0)
     l = sum(i+j+k)
  end function

  integer function do_with_scalars(t1,t2) result(l)
     type(t), intent(in) :: t1,t2
     integer :: i(2),j(2),k(2)
     i(1) = max(t1%i,0); i(2) = max(t2%i,0)
     j(1) = max(t1%j,0); j(2) = max(t2%j,0)
     k(1) = max(t1%k,0); k(2) = max(t2%k,0)
     l = sum(i+j+k)
  end function


end module tmod

program test
   use tmod
   implicit none

   integer, parameter :: n = 1000
   type(t), allocatable :: ts(:)
   integer :: j(n),choose(2),i,k(n)
   real :: x(2)

   ! Initialize with anything
   allocate(ts(n));
   do i=1,n
     ts(i) = t(i,2*i,3*i,[(i,i=1,3)],[(2*i,i=1,20)])
   end do

   ! Do several calls
   do i=1,n
     call random_number(x); choose = ceiling(x*n)

     ! [leak #1]
     j(i) = do_with_array(ts(choose)) ! [#1] MEMORY LEAK

     ! no leak ever
     k(i) = do_with_scalars(ts(choose(1)),ts(choose(2)))
   end do
   print *, 'sum=',sum(j)

   ! [leak #2] happens if ts is not deallocated. Shouldn't a program work like
a
   ! subroutine, and deallocate everything that's going out of scope?
   deallocate(ts)

end program test

The results with valgrind are: 

[perini1@srv0 ~]$ valgrind --tool=memcheck --leak-check=yes --track-origins=yes
./a.out
==49159== Memcheck, a memory error detector
==49159== Copyright (C) 2002-2012, and GNU GPL'd, by Julian Seward et al.
==49159== Using Valgrind-3.8.1 and LibVEX; rerun with -h for copyright info
==49159== Command: ./a.out
==49159==
 sum=     5960916
==49159==
==49159== HEAP SUMMARY:
==49159==     in use at exit: 197,026 bytes in 4,001 blocks
==49159==   total heap usage: 6,023 allocs, 2,022 frees, 446,610 bytes
allocated
==49159==
==49159== 24,000 bytes in 2,000 blocks are definitely lost in loss record 2 of
3
==49159==    at 0x4C28A2E: malloc (vg_replace_malloc.c:270)
==49159==    by 0x402204: MAIN__ (test_leak.f90:55)
==49159==    by 0x4026C9: main (test_leak.f90:36)
==49159==
==49159== 160,000 bytes in 2,000 blocks are definitely lost in loss record 3 of
3
==49159==    at 0x4C28A2E: malloc (vg_replace_malloc.c:270)
==49159==    by 0x402337: MAIN__ (test_leak.f90:55)
==49159==    by 0x4026C9: main (test_leak.f90:36)
==49159==
==49159== LEAK SUMMARY:
==49159==    definitely lost: 184,000 bytes in 4,000 blocks
==49159==    indirectly lost: 0 bytes in 0 blocks
==49159==      possibly lost: 0 bytes in 0 blocks
==49159==    still reachable: 13,026 bytes in 1 blocks
==49159==         suppressed: 0 bytes in 0 blocks
==49159== Reachable blocks (those to which a pointer was found) are not shown.
==49159== To see them, rerun with: --leak-check=full --show-reachable=yes
==49159==
==49159== For counts of detected and suppressed errors, rerun with: -v
==49159== ERROR SUMMARY: 2 errors from 2 contexts (suppressed: 8 from 6)
Profiling timer expired

^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/106750] Memory leak calling array slice of derived type containing `allocatable` entries
  2022-08-26  9:37 [Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries federico.perini at gmail dot com
@ 2022-08-30 18:59 ` anlauf at gcc dot gnu.org
  2022-08-30 19:05 ` anlauf at gcc dot gnu.org
                   ` (2 subsequent siblings)
  3 siblings, 0 replies; 5+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-08-30 18:59 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750

anlauf at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
   Last reconfirmed|                            |2022-08-30
     Ever confirmed|0                           |1
           Keywords|                            |wrong-code
             Status|UNCONFIRMED                 |NEW
                 CC|                            |anlauf at gcc dot gnu.org

--- Comment #1 from anlauf at gcc dot gnu.org ---
Confirmed.  The memory leak comes from not deallocating the temporary
when we have a vector index.  OTOH using an equivalent array constructor
creates the necessary free()'s, as can be seen from the dump.

Reduced testcase:

program test
  implicit none

  type :: t
     integer, allocatable :: a(:)
  end type t

  integer, parameter   :: n = 100
  type(t), allocatable :: ts(:)
  integer :: j(n),i

  allocate(ts(1))
  ts(1)  = t([1,2,3])

  do i=1,n
     j(i) = do_with_array([ts(1),ts(1)]) ! no leak
!    j(i) = do_with_array( ts([1,1])   ) ! MEMORY LEAK
  end do
  print *, 'sum=',sum(j)
  deallocate(ts)

contains

  integer function do_with_array(ts) result(l)
    type(t), intent(in) :: ts(:)
    l = 1
  end function

end program test

^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/106750] Memory leak calling array slice of derived type containing `allocatable` entries
  2022-08-26  9:37 [Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries federico.perini at gmail dot com
  2022-08-30 18:59 ` [Bug fortran/106750] Memory leak calling array slice " anlauf at gcc dot gnu.org
@ 2022-08-30 19:05 ` anlauf at gcc dot gnu.org
  2022-08-31 10:46 ` federico.perini at gmail dot com
  2022-09-11 20:11 ` mikael at gcc dot gnu.org
  3 siblings, 0 replies; 5+ messages in thread
From: anlauf at gcc dot gnu.org @ 2022-08-30 19:05 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750

--- Comment #2 from anlauf at gcc dot gnu.org ---
If you need a workaround, replace:

     j(i) = do_with_array(ts(choose)) ! [#1] MEMORY LEAK

by

     j(i) = do_with_array([ts(choose)]) ! [#1] no more MEMORY LEAK

^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/106750] Memory leak calling array slice of derived type containing `allocatable` entries
  2022-08-26  9:37 [Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries federico.perini at gmail dot com
  2022-08-30 18:59 ` [Bug fortran/106750] Memory leak calling array slice " anlauf at gcc dot gnu.org
  2022-08-30 19:05 ` anlauf at gcc dot gnu.org
@ 2022-08-31 10:46 ` federico.perini at gmail dot com
  2022-09-11 20:11 ` mikael at gcc dot gnu.org
  3 siblings, 0 replies; 5+ messages in thread
From: federico.perini at gmail dot com @ 2022-08-31 10:46 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750

--- Comment #3 from federico <federico.perini at gmail dot com> ---
Thank you for checking this. 
So if I make the temporary array explicit, the leak goes away. 

In the case of the example i.e. 1) fixed-size and 2) very few elements are
passed to the routine, it seems it would just be better to pass them as
scalars, to avoid any temporaries from being at all created: 


     j(i) = do_with_scalars(ts(choose(1)),ts(choose(2))) ! no more MEMORY LEAK

^ permalink raw reply	[flat|nested] 5+ messages in thread

* [Bug fortran/106750] Memory leak calling array slice of derived type containing `allocatable` entries
  2022-08-26  9:37 [Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries federico.perini at gmail dot com
                   ` (2 preceding siblings ...)
  2022-08-31 10:46 ` federico.perini at gmail dot com
@ 2022-09-11 20:11 ` mikael at gcc dot gnu.org
  3 siblings, 0 replies; 5+ messages in thread
From: mikael at gcc dot gnu.org @ 2022-09-11 20:11 UTC (permalink / raw)
  To: gcc-bugs

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106750

Mikael Morin <mikael at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |mikael at gcc dot gnu.org

--- Comment #4 from Mikael Morin <mikael at gcc dot gnu.org> ---
Regarding the other "leak" from the original test:

(In reply to federico from comment #0)
> 
> program test
  (...)
>    type(t), allocatable :: ts(:)
  (...)
>    ! [leak #2] happens if ts is not deallocated. Shouldn't a program work
> like a
>    ! subroutine, and deallocate everything that's going out of scope?
>    deallocate(ts)
> 
> end program test
> 

Not automatically deallocating is the correct behavior here, I think:

> A variable, (...) declared in the scoping unit of a main program, module, or
> submodule implicitly has the SAVE attribute
   => TS has the save attribute.

> The SAVE attribute specifies that a local variable of a program unit or 
> subprogram retains its association status, allocation status, definition 
> status, and value after execution of a RETURN or END statement (...).
   => TS is not deallocated at the end of the program

> When the execution of a procedure is terminated by execution of a RETURN or 
> END statement, an unsaved allocatable local variable of the procedure retains
> its allocation and definition status if it is a function result or a
> subobject thereof; otherwise, if it is allocated it will be deallocated.
   => this doesn’t apply as TS has the save attribute.

^ permalink raw reply	[flat|nested] 5+ messages in thread

end of thread, other threads:[~2022-09-11 20:11 UTC | newest]

Thread overview: 5+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2022-08-26  9:37 [Bug fortran/106750] New: Memory leak calling section of derived type containing `allocatable` entries federico.perini at gmail dot com
2022-08-30 18:59 ` [Bug fortran/106750] Memory leak calling array slice " anlauf at gcc dot gnu.org
2022-08-30 19:05 ` anlauf at gcc dot gnu.org
2022-08-31 10:46 ` federico.perini at gmail dot com
2022-09-11 20:11 ` mikael at gcc dot gnu.org

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox;
as well as URLs for read-only IMAP folder(s) and NNTP newsgroup(s).