public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/40850]  New: "double free or corruption" returning derived types with allocatable components
@ 2009-07-24 19:35 mrestelli at gmail dot com
  2009-07-25  7:33 ` [Bug fortran/40850] " burnus at gcc dot gnu dot org
                   ` (8 more replies)
  0 siblings, 9 replies; 10+ messages in thread
From: mrestelli at gmail dot com @ 2009-07-24 19:35 UTC (permalink / raw)
  To: gcc-bugs

The attached code produces an error at runtime:

System:
Linux 2.6.27-gentoo-r8 x86_64 AMD Turion(tm) 64 Mobile Technology ML-32
AuthenticAMD GNU/Linux

$ gfortran bug.f90 -o bug

$ ./bug
*** glibc detected *** ./bug: double free or corruption (fasttop):
0x000000000060a5b0 ***
======= Backtrace: =========
/lib/libc.so.6[0x7f516d97a468]
/lib/libc.so.6(cfree+0x76)[0x7f516d97bfa6]
./bug[0x40272a]
./bug[0x40283c]
/lib/libc.so.6(__libc_start_main+0xe6)[0x7f516d9255c6]
./bug[0x4007b9]
[...]
Aborted



module mod_all

 implicit none

 public :: &
   t2, new2, operator(+)

 private

 type t1
   integer :: n1
   integer, allocatable :: d1(:)
 end type t1

 type t2
   integer :: n2
   type(t1), allocatable :: d2(:)
 end type t2

 interface operator(+)
   module procedure add
 end interface

 interface new2
   module procedure new2, new2_2
 end interface 

contains

!-----------------------------------------------------------------------

 pure function new1(d1) result(m)
  integer, intent(in) :: d1(:)
  type(t1) :: m

   m%n1 = size(d1)
   allocate(m%d1(m%n1))
   m%d1 = d1

 end function new1

!-----------------------------------------------------------------------

 pure function new2(d2) result(p)
  type(t1), intent(in) :: d2(:)
  type(t2) :: p

   p%n2 = size(d2)
   allocate(p%d2(p%n2))
   p%d2 = d2

 end function new2

!-----------------------------------------------------------------------

 pure function new2_2() result(p)
  type(t2) :: p

   p = new2( (/ new1((/1,1/)) /) )
 end function new2_2

!-----------------------------------------------------------------------

 elemental function add(p1,p2) result(p)
  type(t2), intent(in) :: p1,p2
  type(t2) :: p

   p = new2((/ p1%d2 , p2%d2 /))

 end function add

!-----------------------------------------------------------------------

end module mod_all

!-----------------------------------------------------------------------

program a_main

 use mod_all

 type(t2) :: q(3)

  q(1) = new2()
  q(2) = new2()

  q(3) = q(2) + q(1)

end program a_main


-- 
           Summary: "double free or corruption" returning derived types with
                    allocatable components
           Product: gcc
           Version: unknown
            Status: UNCONFIRMED
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned at gcc dot gnu dot org
        ReportedBy: mrestelli at gmail dot com
 GCC build triplet: gcc version 4.5.0 20090724
  GCC host triplet: Linux 2.6.27-gentoo-r8 x86_64 AMD
GCC target triplet: x86_64-unknown-linux-gnu


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


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

* [Bug fortran/40850] "double free or corruption" returning derived types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
@ 2009-07-25  7:33 ` burnus at gcc dot gnu dot org
  2009-11-27 14:28 ` mrestelli at gmail dot com
                   ` (7 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: burnus at gcc dot gnu dot org @ 2009-07-25  7:33 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #1 from burnus at gcc dot gnu dot org  2009-07-25 07:32 -------
CONFIRM - happens with 4.2/4.3/4.4/4.5.

==13529== Invalid read of size 8
==13529==    at 0x400F2A: __mod_all_MOD_add (in /dev/shm/a.out)

==13529==  Address 0x58d56c8 is 8 bytes inside a block of size 112 free'd
==13529==    at 0x4C23EEE: free (vg_replace_malloc.c:323)
==13529==    by 0x400EB8: __mod_all_MOD_add (in /dev/shm/a.out)


-- 

burnus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
     Ever Confirmed|0                           |1
   Last reconfirmed|0000-00-00 00:00:00         |2009-07-25 07:32:47
               date|                            |


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


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

* [Bug fortran/40850] "double free or corruption" returning derived types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
  2009-07-25  7:33 ` [Bug fortran/40850] " burnus at gcc dot gnu dot org
@ 2009-11-27 14:28 ` mrestelli at gmail dot com
  2009-11-27 14:45 ` mrestelli at gmail dot com
                   ` (6 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: mrestelli at gmail dot com @ 2009-11-27 14:28 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #2 from mrestelli at gmail dot com  2009-11-27 14:28 -------


*** This bug has been marked as a duplicate of 41777 ***


-- 

mrestelli at gmail dot com changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |RESOLVED
         Resolution|                            |DUPLICATE


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


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

* [Bug fortran/40850] "double free or corruption" returning derived types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
  2009-07-25  7:33 ` [Bug fortran/40850] " burnus at gcc dot gnu dot org
  2009-11-27 14:28 ` mrestelli at gmail dot com
@ 2009-11-27 14:45 ` mrestelli at gmail dot com
  2009-12-06 18:15 ` [Bug fortran/40850] double free in nested " dfranke at gcc dot gnu dot org
                   ` (5 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: mrestelli at gmail dot com @ 2009-11-27 14:45 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #3 from mrestelli at gmail dot com  2009-11-27 14:45 -------
(In reply to comment #2)
> 
> *** This bug has been marked as a duplicate of 41777 ***
> 

Sorry! I hit something accidentally on my keyboard, I didn't mean
marking this bug as a duplicate at all...

Apologies!


-- 

mrestelli at gmail dot com changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|RESOLVED                    |REOPENED
         Resolution|DUPLICATE                   |


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


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

* [Bug fortran/40850] double free in nested types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
                   ` (2 preceding siblings ...)
  2009-11-27 14:45 ` mrestelli at gmail dot com
@ 2009-12-06 18:15 ` dfranke at gcc dot gnu dot org
  2009-12-07 21:01 ` janus at gcc dot gnu dot org
                   ` (4 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: dfranke at gcc dot gnu dot org @ 2009-12-06 18:15 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #4 from dfranke at gcc dot gnu dot org  2009-12-06 18:15 -------
Reduced testcase:

  type t1
    integer, allocatable :: d1(:)
  end type t1
  type t2
    type(t1), allocatable :: d2(:)
  end type t2
  type(t2) :: a, b

  a = new2( (/ new1((/1,1/)) /) )
  b = new2( (/ a%d2 , a%d2 /) )

contains
  pure type(t1) function new1(d1)
    integer, intent(in) :: d1(:)
    allocate(new1%d1(size(d1)))
    new1%d1 = d1
  end function
  pure type(t2) function new2(d2)
    type(t1), intent(in) :: d2(:)
    allocate(new2%d2(size(d2)))
    new2%d2 = d2
  end function
end

The dump still has about 800 lines - somewhat hard to tell what's going on.
Adding PaulT as CC.


-- 

dfranke at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |dfranke at gcc dot gnu dot
                   |                            |org, pault at gcc dot gnu
                   |                            |dot org
   Last reconfirmed|2009-07-25 07:32:47         |2009-12-06 18:15:24
               date|                            |
            Summary|"double free or corruption" |double free in nested types
                   |returning derived types with|with allocatable components
                   |allocatable components      |


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


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

* [Bug fortran/40850] double free in nested types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
                   ` (3 preceding siblings ...)
  2009-12-06 18:15 ` [Bug fortran/40850] double free in nested " dfranke at gcc dot gnu dot org
@ 2009-12-07 21:01 ` janus at gcc dot gnu dot org
  2010-01-07 14:49 ` pault at gcc dot gnu dot org
                   ` (3 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: janus at gcc dot gnu dot org @ 2009-12-07 21:01 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #5 from janus at gcc dot gnu dot org  2009-12-07 21:00 -------
Further reduced test case:


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

  allocate(a(2))
  call sub( (/ a /) )

contains

  subroutine sub(b)
    type(t) :: b(:)
  end subroutine

end


The dump still has more than 200 lines and five __builtin_free's.


-- 

janus at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |janus at gcc dot gnu dot org
   Last reconfirmed|2009-12-06 18:15:24         |2009-12-07 21:00:41
               date|                            |


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


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

* [Bug fortran/40850] double free in nested types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
                   ` (4 preceding siblings ...)
  2009-12-07 21:01 ` janus at gcc dot gnu dot org
@ 2010-01-07 14:49 ` pault at gcc dot gnu dot org
  2010-01-29 18:24 ` mrestelli at gmail dot com
                   ` (2 subsequent siblings)
  8 siblings, 0 replies; 10+ messages in thread
From: pault at gcc dot gnu dot org @ 2010-01-07 14:49 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #6 from pault at gcc dot gnu dot org  2010-01-07 14:49 -------
I had better add this to the list!

Paul


-- 

pault at gcc dot gnu dot org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
         AssignedTo|unassigned at gcc dot gnu   |pault at gcc dot gnu dot org
                   |dot org                     |
             Status|REOPENED                    |ASSIGNED
   Last reconfirmed|2009-12-07 21:00:41         |2010-01-07 14:49:06
               date|                            |


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


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

* [Bug fortran/40850] double free in nested types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
                   ` (5 preceding siblings ...)
  2010-01-07 14:49 ` pault at gcc dot gnu dot org
@ 2010-01-29 18:24 ` mrestelli at gmail dot com
  2010-02-12 13:51 ` domob at gcc dot gnu dot org
  2010-03-07 17:24 ` dominiq at lps dot ens dot fr
  8 siblings, 0 replies; 10+ messages in thread
From: mrestelli at gmail dot com @ 2010-01-29 18:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #7 from mrestelli at gmail dot com  2010-01-29 18:24 -------
(In reply to comment #5)
> Further reduced test case:
> 
> 
>   type t
>     integer, allocatable :: d(:)
>   end type
>   type(t), allocatable :: a(:)
> 
>   allocate(a(2))
>   call sub( (/ a /) )
> 
> contains
> 
>   subroutine sub(b)
>     type(t) :: b(:)
>   end subroutine
> 
> end
> 
> 
> The dump still has more than 200 lines and five __builtin_free's.
> 


Not sure if this is correct or useful, since I don't know the gfortran
internals at all, but anyway, mostly out of curiosity: my impression
is that the problem is in the lines 187-222 of the
-fdump-tree-original output file. More precisely (starting with line
186):


    sub (&atmp.6);
Here we free atmp.3.data (without worrying about the allocation status
of the elements)
    {
      void * D.1574;

      D.1574 = (void *) atmp.3.data;
      if (D.1574 != 0B)
        {
          __builtin_free (D.1574);
        }
    }
Here we free atmp.6.data (again, without worrying about the allocation
status of the elements)
    {
      void * D.1593;

      D.1593 = (void *) atmp.6.data;
      if (D.1593 != 0B)
        {
          __builtin_free (D.1593);
        }
    }
Now we look at the elements of atmp.6.data to check whether we have to
free them too. It seems to the me that this block should be moved
before the previous one (or eliminated at all, as it is done for
atmp.3.data)
    if ((struct t[0:] * restrict) atmp.6.data != 0B)
      {
        D.1596 = (atmp.6.dim[0].ubound - atmp.6.dim[0].lbound) + 1;
        D.1597 = atmp.6.dim[0].stride * D.1596;
        D.1598 = D.1597 + -1;
        S.8 = 0;
        while (1)
          {
            if (S.8 > D.1598) goto L.5;
Here we access memory that has already been freed
            if ((*(struct t[0:] * restrict) atmp.6.data)[S.8].d.data != 0B)
              {
                __builtin_free ((void *) (*(struct t[0:] * restrict)
atmp.6.data)[S.8].d.data);
              }
            (*(struct t[0:] * restrict) atmp.6.data)[S.8].d.data = 0B;
            S.8 = S.8 + 1;
          }
        L.5:;
      }


-- 


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


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

* [Bug fortran/40850] double free in nested types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
                   ` (6 preceding siblings ...)
  2010-01-29 18:24 ` mrestelli at gmail dot com
@ 2010-02-12 13:51 ` domob at gcc dot gnu dot org
  2010-03-07 17:24 ` dominiq at lps dot ens dot fr
  8 siblings, 0 replies; 10+ messages in thread
From: domob at gcc dot gnu dot org @ 2010-02-12 13:51 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #8 from domob at gcc dot gnu dot org  2010-02-12 13:51 -------
I hit this bug, too, it seems.  My reduced test-case:

PROGRAM analysis
  IMPLICIT NONE

  TYPE numlist
    REAL, ALLOCATABLE :: nums(:)
  END TYPE numlist

  TYPE(numlist) :: lines
  ALLOCATE (lines%nums(1))

  CALL test ((/ lines /))

CONTAINS

  SUBROUTINE test (vec)
    TYPE(numlist), INTENT(IN) :: vec(:)
  END SUbROUTINE test

END PROGRAM analysis

This produces 126 lines of -fdump-tree-original, so I hope it may help here as
being "simpler" than the one posted by Janus (it seems).


-- 


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


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

* [Bug fortran/40850] double free in nested types with allocatable components
  2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
                   ` (7 preceding siblings ...)
  2010-02-12 13:51 ` domob at gcc dot gnu dot org
@ 2010-03-07 17:24 ` dominiq at lps dot ens dot fr
  8 siblings, 0 replies; 10+ messages in thread
From: dominiq at lps dot ens dot fr @ 2010-03-07 17:24 UTC (permalink / raw)
  To: gcc-bugs



------- Comment #9 from dominiq at lps dot ens dot fr  2010-03-07 17:24 -------
I just noticed that using -Warray-temporaries gives the warning twice. For the
test in comment #8, I get

[macbook] f90/bug% gfc -Warray-temporaries -fcheck=all pr40850_3.f90
pr40850_3.f90:11.13:

  CALL test ((/ lines /))
             1
Warning: Creating array temporary at (1)
pr40850_3.f90:11.13:

  CALL test ((/ lines /))
             1
Warning: Creating array temporary at (1)
[macbook] f90/bug% a.out
a.out(35149) malloc: *** error for object 0x100201010: pointer being freed was
not allocated
*** set a breakpoint in malloc_error_break to debug
Abort


-- 


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


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

end of thread, other threads:[~2010-03-07 17:24 UTC | newest]

Thread overview: 10+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2009-07-24 19:35 [Bug fortran/40850] New: "double free or corruption" returning derived types with allocatable components mrestelli at gmail dot com
2009-07-25  7:33 ` [Bug fortran/40850] " burnus at gcc dot gnu dot org
2009-11-27 14:28 ` mrestelli at gmail dot com
2009-11-27 14:45 ` mrestelli at gmail dot com
2009-12-06 18:15 ` [Bug fortran/40850] double free in nested " dfranke at gcc dot gnu dot org
2009-12-07 21:01 ` janus at gcc dot gnu dot org
2010-01-07 14:49 ` pault at gcc dot gnu dot org
2010-01-29 18:24 ` mrestelli at gmail dot com
2010-02-12 13:51 ` domob at gcc dot gnu dot org
2010-03-07 17:24 ` dominiq at lps dot ens dot fr

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).