public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/41936]  New: Memory leakage with allocatables and user-defined operators
@ 2009-11-04  9:01 burnus at gcc dot gnu dot org
  2009-11-12 13:51 ` [Bug fortran/41936] " pault at gcc dot gnu dot org
  0 siblings, 1 reply; 10+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-11-04  9:01 UTC (permalink / raw)
  To: gcc-bugs

Reported by Paul van Delst at
http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/196e69ca0ed38f98

Seemingly, gfortran leaks memory with allocatables and user-defined operators.
Might be a duplicate of some other bug - I have not yet check thoroughly. I
also have not checked the code myself. 

!<-----begin module my_type_define----->
module my_type_define
  implicit none

  private
  public :: my_type
  public :: assignment(=)
  public :: operator(+)
  public :: my_associated
  public :: my_destroy
  public :: my_create
  public :: my_inspect

  interface assignment(=)
    module procedure my_assign
  end interface assignment(=)
  interface operator(+)
    module procedure my_add
  end interface operator(+)

  type :: my_type
    integer :: n = 0
    real, allocatable :: x(:), y(:), z(:)
  end type my_type

contains

  ! Public

  elemental function my_associated( my ) result( status )
    type(my_type), intent(in) :: my
    logical :: status
    ! test the structure members
    status = allocated(my%x) .or. allocated(my%y) .or. allocated(my%z)
  end function my_associated

  elemental subroutine my_destroy( my )
    type(my_type), intent(out) :: my
  end subroutine my_destroy

  elemental subroutine my_create( my, n )
    type(my_type), intent(out) :: my
    integer,       intent(in)  :: n
    integer :: alloc_stat
    ! check input
    if ( n < 1 ) return
    ! perform the allocation
    allocate( my%x(n), my%y(n), my%z(n), stat=alloc_stat )
    ! initialise
    if ( alloc_stat == 0 ) then
      ! ...dimension
      my%n = n
      ! ...arrays
      my%x = 0.0
      my%y = 0.0
      my%z = 0.0
    end if
  end subroutine my_create

  subroutine my_inspect( my )
    type(my_type), intent(in) :: my
    if ( .not. my_associated( my ) ) return
    write(*,'(5x,"x:")'); write(*,'(5(1x,es13.6))') my%x
    write(*,'(5x,"y:")'); write(*,'(5(1x,es13.6))') my%y
    write(*,'(5x,"z:")'); write(*,'(5(1x,es13.6))') my%z
  end subroutine my_inspect

  ! Private

  elemental subroutine my_assign( copy, original )
    type(my_type),  intent(out) :: copy
    type(my_type),  intent(in)  :: original
    ! if input structure not used, do nothing
    if ( .not. my_associated( original ) ) return
    ! create the output structure
    call my_create( copy, original%n )
    ! ...return if no allocation performed
    if ( .not. my_associated( copy ) ) return
    ! copy data
    copy%x = original%x
    copy%y = original%y
    copy%z = original%z
  end subroutine my_assign

  elemental function my_add( my1, my2 ) result( mysum )
    type(my_type), intent(in) :: my1, my2
    type(my_type) :: mysum
    ! copy the first structure
    mysum = my1
    ! and add its components to the second one
    mysum%x = mysum%x + my2%x
    mysum%y = mysum%y + my2%y
    mysum%z = mysum%z + my2%z
  end function my_add

end module my_type_define
!<-----end module my_type_define----->

!<-----begin program my_test----->
program my_test
  use my_type_define
  implicit none

  integer, parameter :: n = 3

  integer :: i
  type(my_type) :: a, b
  type(my_type) :: c(n), d(n)

  ! Scalar test
  call my_create(a, 10)
  a%x = 1.0
  a%y = 2.0
  a%z = 3.0
  write(*,'(/,"A")')
  call my_inspect(a)
  b = a
  write(*,'(/,"B")')
  call my_inspect(b)
  a = a + b
  write(*,'(/,"A = A + B")')
  call my_inspect(a)
  call my_destroy(a)
  call my_destroy(b)

  ! Rank-1 test
  call my_create(c, 10)
  do i = 1, n
    c(i)%x = 1.0
    c(i)%y = 2.0
    c(i)%z = 3.0
    write(*,'(/,"C(",i0,")")') i
    call my_inspect(c(i))
  end do
  d = c
  do i = 1, n
    write(*,'(/,"D(",i0,")")') i
    call my_inspect(d(i))
  end do
  c = c + d  ! commenting this line makes memory leaks go away.
  do i = 1, n
    write(*,'(/,"C(",i0,") + D(",i0,")")') i, i
    call my_inspect(c(i))
  end do
  call my_destroy(c)
  call my_destroy(d)
end program my_test
!<-----end program my_test----->

!<-----begin valgrind output----->
==356==
==356== ERROR SUMMARY: 0 errors from 0 contexts (suppressed: 17 from 1)
==356== malloc/free: in use at exit: 360 bytes in 9 blocks.
==356== malloc/free: 146 allocs, 137 frees, 225,998 bytes allocated.
==356== For counts of detected errors, rerun with: -v
==356== searching for pointers to 9 not-freed blocks.
==356== checked 70,540 bytes.
==356==
==356== 120 bytes in 3 blocks are definitely lost in loss record 1 of 3
==356==    at 0x40053C0: malloc (vg_replace_malloc.c:149)
==356==    by 0x804921F: __my_type_define_MOD_my_create (in a.out)
==356==    by 0x8048AE0: __my_type_define_MOD_my_assign (in a.out)
==356==    by 0x80486C6: __my_type_define_MOD_my_add (in a.out)
==356==    by 0x8049E64: MAIN__ (in a.out)
==356==    by 0x804A20A: main (fmain.c:21)
==356==
==356==
==356== 120 bytes in 3 blocks are definitely lost in loss record 2 of 3
==356==    at 0x40053C0: malloc (vg_replace_malloc.c:149)
==356==    by 0x804912A: __my_type_define_MOD_my_create (in a.out)
==356==    by 0x8048AE0: __my_type_define_MOD_my_assign (in a.out)
==356==    by 0x80486C6: __my_type_define_MOD_my_add (in a.out)
==356==    by 0x8049E64: MAIN__ (in a.out)
==356==    by 0x804A20A: main (fmain.c:21)
==356==
==356==
==356== 120 bytes in 3 blocks are definitely lost in loss record 3 of 3
==356==    at 0x40053C0: malloc (vg_replace_malloc.c:149)
==356==    by 0x8049035: __my_type_define_MOD_my_create (in a.out)
==356==    by 0x8048AE0: __my_type_define_MOD_my_assign (in a.out)
==356==    by 0x80486C6: __my_type_define_MOD_my_add (in a.out)
==356==    by 0x8049E64: MAIN__ (in a.out)
==356==    by 0x804A20A: main (fmain.c:21)
==356==
==356== LEAK SUMMARY:
==356==    definitely lost: 360 bytes in 9 blocks.
==356==      possibly lost: 0 bytes in 0 blocks.
==356==    still reachable: 0 bytes in 0 blocks.
==356==         suppressed: 0 bytes in 0 blocks.
!<-----end valgrind output----->


-- 
           Summary: Memory leakage with allocatables and user-defined
                    operators
           Product: gcc
           Version: 4.5.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: burnus at gcc dot gnu dot org


http://gcc.gnu.org/bugzilla/show_bug.cgi?id=41936


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

end of thread, other threads:[~2014-07-07 14:00 UTC | newest]

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
     [not found] <bug-41936-4@http.gcc.gnu.org/bugzilla/>
2011-02-28 21:59 ` [Bug fortran/41936] Memory leakage with allocatables and user-defined operators mikael at gcc dot gnu.org
2014-04-27 14:05 ` dominiq at lps dot ens.fr
2014-04-27 14:32 ` burnus at gcc dot gnu.org
2014-04-27 14:47 ` dominiq at lps dot ens.fr
2014-05-04 10:06 ` dominiq at lps dot ens.fr
2014-06-10 11:43 ` dominiq at gcc dot gnu.org
2014-07-07 12:33 ` dominiq at gcc dot gnu.org
2014-07-07 14:00 ` dominiq at lps dot ens.fr
2014-07-07 14:00 ` dominiq at lps dot ens.fr
2009-11-04  9:01 [Bug fortran/41936] New: " burnus at gcc dot gnu dot org
2009-11-12 13:51 ` [Bug fortran/41936] " pault at gcc dot gnu dot 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).