public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
@ 2012-09-18 15:24 burnus at gcc dot gnu.org
  2012-09-19  8:18 ` [Bug fortran/54618] " burnus at gcc dot gnu.org
                   ` (20 more replies)
  0 siblings, 21 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-18 15:24 UTC (permalink / raw)
  To: gcc-bugs

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

             Bug #: 54618
           Summary: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and
                    OPTIONAL or ALLOCATABLE
    Classification: Unclassified
           Product: gcc
           Version: 4.8.0
            Status: UNCONFIRMED
          Keywords: wrong-code
          Severity: normal
          Priority: P3
         Component: fortran
        AssignedTo: unassigned@gcc.gnu.org
        ReportedBy: burnus@gcc.gnu.org
                CC: janus@gcc.gnu.org


The following program gives an ICE because one has:


f (struct __class_p_T * y)
{
  __builtin_memcpy (y->_data, y->_vptr->_def_init, y->_vptr->_size);
}


The code lacks an "if (y->_data)" check via gfc_conv_expr_present in
init_intent_out_dt.


program p
  type t
  end type t

  type(t) :: x

  call f(x)
  call f()
contains
  subroutine f(y)
    class(t), intent(out), optional :: y
  end subroutine f
end program p

* * * 

While the following program fails because there is no deallocate/memcpy in f:

f (struct __class_p_T_a & restrict y)
{

}


program p
  type t
  end type t
  type, extends(t):: t2
  end type t2

  class(t), allocatable :: x,y
  allocate (t2 :: x)
  call f(x)
  if (allocated (x) .or. .not. same_type_as (x,y)) call abort()
contains
  subroutine f(y)
    class(t), intent(out), allocatable :: y
  end subroutine f
end program p


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
@ 2012-09-19  8:18 ` burnus at gcc dot gnu.org
  2012-09-19 13:31 ` burnus at gcc dot gnu.org
                   ` (19 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-19  8:18 UTC (permalink / raw)
  To: gcc-bugs

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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

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

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-19 08:18:27 UTC ---
The second issue has to be fixed in trans-expr.c's gfc_conv_procedure_call.

Patch for the first issue.

--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -623,2 +623,12 @@ gfc_trans_class_init_assign (gfc_code *code)
     }
+
+  if (code->expr1->symtree->n.sym->attr.optional
+      || code->expr1->symtree->n.sym->ns->proc_name->attr.entry_master)
+    {
+      tree present = gfc_conv_expr_present (code->expr1->symtree->n.sym);
+      tmp = build3_loc (input_location, COND_EXPR, TREE_TYPE (tmp),
+                       present, tmp,
+                       build_empty_stmt (input_location));
+    }
+
   gfc_add_expr_to_block (&block, tmp);


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
  2012-09-19  8:18 ` [Bug fortran/54618] " burnus at gcc dot gnu.org
@ 2012-09-19 13:31 ` burnus at gcc dot gnu.org
  2012-09-19 17:31 ` burnus at gcc dot gnu.org
                   ` (18 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-19 13:31 UTC (permalink / raw)
  To: gcc-bugs

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

--- Comment #2 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-19 13:31:19 UTC ---
Draft patch for the second issue. Note the FIXME for resetting to the declared
type.

Additionally, the patch fixes only the scalar issue, the same has also to be
done for arrays.

--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -3907,9 +3917,16 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
                     allocated on entry, it must be deallocated.  */
-                 if (fsym && fsym->attr.allocatable
-                     && fsym->attr.intent == INTENT_OUT)
+                 if (fsym && fsym->attr.intent == INTENT_OUT
+                     && (fsym->attr.allocatable
+                         || (fsym->ts.type == BT_CLASS
+                             && CLASS_DATA (e)->attr.allocatable)))
                    {
                      stmtblock_t block;
+                     tree ptr;

                      gfc_init_block  (&block);
-                     tmp = gfc_deallocate_with_status (parmse.expr, NULL_TREE,
+                     ptr = parmse.expr;
+                     if (e->ts.type == BT_CLASS)
+                       ptr = gfc_class_data_get (ptr);
+
+                     tmp = gfc_deallocate_with_status (ptr, NULL_TREE,
                                                        NULL_TREE, NULL_TREE,
@@ -3919,3 +3936,3 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
                      tmp = fold_build2_loc (input_location, MODIFY_EXPR,
-                                            void_type_node, parmse.expr,
+                                            void_type_node, ptr,
                                             null_pointer_node);
@@ -3923,2 +3940,6 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,

+/*                   if (fsym->ts.type == BT_CLASS)
+                       FIXME: Do something similar as
+                       in gfc_trans_class_init_assign.  */
+
                      if (fsym->attr.optional


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
  2012-09-19  8:18 ` [Bug fortran/54618] " burnus at gcc dot gnu.org
  2012-09-19 13:31 ` burnus at gcc dot gnu.org
@ 2012-09-19 17:31 ` burnus at gcc dot gnu.org
  2012-09-19 20:18 ` mikael at gcc dot gnu.org
                   ` (17 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-19 17:31 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #3 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-19 17:31:06 UTC ---
There seem to be other issues with OPTIONAL as well. The following code prints
twice 'T' when it should print 'F' and it segfaults for one version.
I haven't dared to combine it with INTENT(OUT) and/or ALLOCATABLE.

The following program gives the same result with 4.7 as with 4.8 + my patch:

  type t
  end type t
  type(t) :: y, y2(2)
  class(t), allocatable :: z, z2(:)
  allocate (t :: z)
  allocate (t :: z2(2))
!print *, 'Scalars, expected: F F T T T T'
  call s1()   ! OK
  call s1a()  ! -> should print 'F', prints 'T'
  call s1(y)  ! OK
  call s1a(y) ! OK
  call s1(z)  ! OK
  call s1a(z) ! OK
!print *, 'Arrays, expected: F F T T T T'
!  call sa1()   ! Segfault
  call sa1a()   ! -> should print 'F', prints 'T'
  call sa1(y2)  ! OK
  call sa1a(y2) ! OK
  call sa1(z2)  ! OK
  call sa1a(z2) ! OK
contains
 subroutine s1(x)
   class(t), optional :: x
   call s2(x)
 end subroutine s1
 subroutine s1a(x)
   type(t), optional :: x
   call s2(x)
 end subroutine s1a
 subroutine s2(x)
   class(t), optional :: x
   print *, present(x)
 end subroutine s2

 subroutine sa1(x)
   class(t), optional :: x(:)
   call sa2(x)
 end subroutine sa1
 subroutine sa1a(x)
   type(t), optional :: x(:)
   call sa2(x)
 end subroutine sa1a
 subroutine sa2(x)
   class(t), optional :: x(:)
   print *, present(x)
 end subroutine sa2
end

 * * *

The missing bits for the patch in comment 2 are fixable as follows, which
completes the scalar version of the second issue.

--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -3923,2 +3940,15 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,

+                     if (fsym->ts.type == BT_CLASS)
+                       {
+                         gfc_symbol *vtab;
+                         gcc_assert (fsym->ts.u.derived == e->ts.u.derived);
+                         vtab = gfc_find_derived_vtab (fsym->ts.u.derived);
+                         tmp = gfc_get_symbol_decl (vtab);
+                         tmp = gfc_build_addr_expr (NULL_TREE, tmp);
+                         ptr = gfc_class_vptr_get (parmse.expr);
+                         gfc_add_modify (&block, ptr,
+                                         fold_convert (TREE_TYPE (ptr), tmp));
+                         gfc_add_expr_to_block (&block, tmp);
+                       }
+
                      if (fsym->attr.optional


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2012-09-19 17:31 ` burnus at gcc dot gnu.org
@ 2012-09-19 20:18 ` mikael at gcc dot gnu.org
  2012-09-22 17:07 ` burnus at gcc dot gnu.org
                   ` (16 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: mikael at gcc dot gnu.org @ 2012-09-19 20:18 UTC (permalink / raw)
  To: gcc-bugs


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

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> 2012-09-19 20:18:01 UTC ---
Related bug: pr 50981 (which I've never had the courage to finish).


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2012-09-19 20:18 ` mikael at gcc dot gnu.org
@ 2012-09-22 17:07 ` burnus at gcc dot gnu.org
  2012-09-23  6:49 ` burnus at gcc dot gnu.org
                   ` (15 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-22 17:07 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

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

--- Comment #5 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-22 17:06:45 UTC ---
Unreviewed patch: http://gcc.gnu.org/ml/fortran/2012-09/msg00073.html


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2012-09-22 17:07 ` burnus at gcc dot gnu.org
@ 2012-09-23  6:49 ` burnus at gcc dot gnu.org
  2012-09-24 19:05 ` burnus at gcc dot gnu.org
                   ` (14 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-23  6:49 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-23 06:48:56 UTC ---
Author: burnus
Date: Sun Sep 23 06:48:48 2012
New Revision: 191649

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=191649
Log:
2012-09-23  Tobias Burnus  <burnus@net-b.de>

        * parse.c (parse_derived): Don't set attr.alloc_comp
        for pointer components with allocatable subcomps.

        PR fortran/54599
        * resolve.c (resolve_fl_namelist): Remove superfluous
        NULL check.
        * simplify.c (simplify_min_max): Remove unreachable code.
        * trans-array.c (gfc_trans_create_temp_array): Change
        a condition into an assert.

        PR fortran/54618
        * trans-expr.c (gfc_trans_class_init_assign): Guard
        re-setting of the _data by gfc_conv_expr_present.
        (gfc_conv_procedure_call): Fix INTENT(OUT) handling
        for allocatable BT_CLASS.

2012-09-23  Tobias Burnus  <burnus@net-b.de>

        PR fortran/54618
        * gfortran.dg/class_array_14.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/class_array_14.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/parse.c
    trunk/gcc/fortran/resolve.c
    trunk/gcc/fortran/simplify.c
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2012-09-23  6:49 ` burnus at gcc dot gnu.org
@ 2012-09-24 19:05 ` burnus at gcc dot gnu.org
  2012-09-25 14:20 ` burnus at gcc dot gnu.org
                   ` (13 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-24 19:05 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-24 19:05:24 UTC ---
Author: burnus
Date: Mon Sep 24 19:05:18 2012
New Revision: 191676

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=191676
Log:
2012-09-24  Tobias Burnus  <burnus@net-b.de>

        PR fortran/54618
        * trans-expr.c (gfc_conv_procedure_call): Fix INTENT(OUT)
        handling for allocatable BT_CLASS.


Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-expr.c


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2012-09-24 19:05 ` burnus at gcc dot gnu.org
@ 2012-09-25 14:20 ` burnus at gcc dot gnu.org
  2012-09-25 18:37 ` burnus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-25 14:20 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-25 14:19:59 UTC ---
Created attachment 28269
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=28269
OPTIOAL: Draft patch + test case

I have attached a patch which fixes some of the issues with OPTIONAL and CLASS.
The file also contains a test case. Remaining issues with that test case: one
wrong result ("T" instead of "F") and a couple of segmentation faults.

TODO:
- Fix those issues
- Fix CLASS(t), ALLOCATABLE, INTENT(OUT) for arrays (cf. comment 0)

- Check whether there are more issues with intent(out) - or with OPTIONAL, e.g.
with allocatable/pointer or ELEMENTAL. PR 50981 might give some inspiration
what else could be wrong.


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2012-09-25 14:20 ` burnus at gcc dot gnu.org
@ 2012-09-25 18:37 ` burnus at gcc dot gnu.org
  2012-09-26  5:51 ` burnus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-25 18:37 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-25 18:37:26 UTC ---
Created attachment 28275
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=28275
Patch for OPTIONAL

This patch fixes the segfaults of the test case in attachment 28269. It also
avoids the copy back of _data/_vptr for class_to_class when it cannot change.

(Note that this patch also fixes the issues of bug 50981 comment 31 and bug
50981 comment 23.)

Still to do:
- Fix CLASS(t), ALLOCATABLE, INTENT(OUT) for arrays (cf. comment 0)
- More test (cf. comment 8 and bug 50981 comment 36)

And the remaining failure of the test case (attachment 28269): For an absent
actual to a1a1,

   subroutine a1a1(z)
     type(t), optional :: z(:)
     call a2(z)

a present PRESENT(x) check in a2 is wrongly .TRUE. The present check is
  if (x != 0B && (struct t[0:] *) x->_data.data != 0B)

The problem is that the argument in a1a1 is handled as:
    parm.5.data = (void *) &(*z.0)[0];
    class.4._data = parm.5;
    a2 (&class.4);


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2012-09-25 18:37 ` burnus at gcc dot gnu.org
@ 2012-09-26  5:51 ` burnus at gcc dot gnu.org
  2012-09-30 12:51 ` dominiq at lps dot ens.fr
                   ` (10 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-26  5:51 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
  Attachment #28275|0                           |1
        is obsolete|                            |

--- Comment #10 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-26 05:51:10 UTC ---
Created attachment 28278
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=28278
Patch for OPTIONAL  (this time really a patch)


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2012-09-26  5:51 ` burnus at gcc dot gnu.org
@ 2012-09-30 12:51 ` dominiq at lps dot ens.fr
  2012-09-30 17:01 ` burnus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: dominiq at lps dot ens.fr @ 2012-09-30 12:51 UTC (permalink / raw)
  To: gcc-bugs


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

Dominique d'Humieres <dominiq at lps dot ens.fr> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2012-09-30
     Ever Confirmed|0                           |1

--- Comment #11 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2012-09-30 12:51:11 UTC ---
With the patch in comment #10, gfortran (otherwise clean r191847) miscompiles
gfortran.dg/class_array_7.f03. If I replace the "if ... abort()" with prints, I
get

 a is extended_type
 tmp is base_type
 a is extended_type
a.out(83666) malloc: *** error for object 0x100200f80: pointer being freed was
not allocated

or

[macbook] f90/bug% valgrind a.out
==96855== Memcheck, a memory error detector
==96855== Copyright (C) 2002-2011, and GNU GPL'd, by Julian Seward et al.
==96855== Using Valgrind-3.7.0 and LibVEX; rerun with -h for copyright info
==96855== Command: a.out
==96855== 
 a is extended_type
 tmp is base_type
==96855== Invalid read of size 4
==96855==    at 0x100001782: __realloc_MOD_assign (class_array_7_db.f90:25)
==96855==    by 0x100001685: __realloc_MOD_reallocate (class_array_7_db.f90:34)
==96855==    by 0x100001A61: MAIN__ (class_array_7_db.f90:57)
==96855==    by 0x100001BD5: main (class_array_7_db.f90:50)
==96855==  Address 0x100442408 is 0 bytes after a block of size 40 alloc'd
==96855==    at 0x100013679: malloc (vg_replace_malloc.c:266)
==96855==    by 0x100001830: MAIN__ (class_array_7_db.f90:54)
==96855==    by 0x100001BD5: main (class_array_7_db.f90:50)
==96855== 
 a is extended_type
==96855== Invalid free() / delete / delete[] / realloc()
==96855==    at 0x10001352D: free (vg_replace_malloc.c:430)
==96855==    by 0x100001B9D: MAIN__ (class_array_7_db.f90:60)
==96855==    by 0x100001BD5: main (class_array_7_db.f90:50)
==96855==  Address 0x1004423e0 is 0 bytes inside a block of size 40 free'd
==96855==    at 0x10001352D: free (vg_replace_malloc.c:430)
==96855==    by 0x1000016BB: __realloc_MOD_reallocate (class_array_7_db.f90:35)
==96855==    by 0x100001A61: MAIN__ (class_array_7_db.f90:57)
==96855==    by 0x100001BD5: main (class_array_7_db.f90:50)
==96855== 
==96855== 
==96855== HEAP SUMMARY:
==96855==     in use at exit: 168 bytes in 2 blocks
==96855==   total heap usage: 25 allocs, 24 frees, 7,321 bytes allocated
==96855== 
==96855== LEAK SUMMARY:
==96855==    definitely lost: 80 bytes in 1 blocks
==96855==    indirectly lost: 0 bytes in 0 blocks
==96855==      possibly lost: 0 bytes in 0 blocks
==96855==    still reachable: 0 bytes in 0 blocks
==96855==         suppressed: 88 bytes in 1 blocks
==96855== Rerun with --leak-check=full to see details of leaked memory
==96855== 
==96855== For counts of detected and suppressed errors, rerun with: -v
==96855== ERROR SUMMARY: 6 errors from 2 contexts (suppressed: 0 from 0)

Otherwise the patch works as advertised.


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2012-09-30 12:51 ` dominiq at lps dot ens.fr
@ 2012-09-30 17:01 ` burnus at gcc dot gnu.org
  2012-09-30 18:02 ` burnus at gcc dot gnu.org
                   ` (8 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-30 17:01 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #12 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-30 17:01:26 UTC ---
(In reply to comment #11)
> With the patch in comment #10, gfortran (otherwise clean r191847) miscompiles
> gfortran.dg/class_array_7.f03.

Seems to be fixed by my much extended local version (which still has some
issues related to polymorphic coarrays).


The following issue I see, however, also with GCC 4.7. I think it should be
investigated and seems to be unrelated to my patch:

> ==96855== Invalid read of size 4
> ==96855==    at 0x100001782: __realloc_MOD_assign (class_array_7_db.f90:25)
> ==96855==    by 0x100001685: __realloc_MOD_reallocate (class_array_7_db.f90:34)


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (11 preceding siblings ...)
  2012-09-30 17:01 ` burnus at gcc dot gnu.org
@ 2012-09-30 18:02 ` burnus at gcc dot gnu.org
  2012-10-03 14:20 ` burnus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-09-30 18:02 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
  Attachment #28269|0                           |1
        is obsolete|                            |
  Attachment #28278|0                           |1
        is obsolete|                            |

--- Comment #13 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-09-30 18:02:33 UTC ---
Created attachment 28304
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=28304
Updated OPTIONAL patch

Current version of my OPTIONAL patch, just to make sure that I don't
accidentally delete it locally. It fixes a bunch of issues; however, as the
FIXMEs show, there are still wrong-code (segfault at run time) issues related
to ELEMENTAL, scalar coarrays and possibly another issue.

TODO:
- Fix the OPTIONAL issues mentioned above
- Support packing of assumed-rank arrays
  (see just attached test case; but otherwise an unrelated issue)
- Fix INTENT(OUT) handling for allocatable polymorphic arrays (cf. comment 0)
- Analyse the old issue related to class_array_7.f03 (comment 11, comment 12)


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (12 preceding siblings ...)
  2012-09-30 18:02 ` burnus at gcc dot gnu.org
@ 2012-10-03 14:20 ` burnus at gcc dot gnu.org
  2012-10-03 17:32 ` burnus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-03 14:20 UTC (permalink / raw)
  To: gcc-bugs


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

Tobias Burnus <burnus at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
  Attachment #28304|0                           |1
        is obsolete|                            |

--- Comment #14 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-10-03 14:20:22 UTC ---
Created attachment 28341
  --> http://gcc.gnu.org/bugzilla/attachment.cgi?id=28341
Updated OPTIONAL patch

Current version of my OPTIONAL patch. Changes:
- polymorphic scalar coarray to polymorphic noncoarrays work now
- Much extended test case (and plenty of new FIXMEs)
TODO: Fix those FIXMEs.

Other TODO items:
- Support packing of assumed-rank arrays
  (see just attached test case; but otherwise an unrelated issue)
- Fix INTENT(OUT) handling for allocatable polymorphic arrays (cf. comment 0)
- Analyse the old issue related to class_array_7.f03 (comment 11, comment 12)


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (13 preceding siblings ...)
  2012-10-03 14:20 ` burnus at gcc dot gnu.org
@ 2012-10-03 17:32 ` burnus at gcc dot gnu.org
  2012-10-16 13:02 ` burnus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-03 17:32 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #15 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-10-03 17:32:01 UTC ---
(In reply to comment #14)
> - Fix INTENT(OUT) handling for allocatable polymorphic arrays (cf. comment 0)

Reminder: Check that this also handles (non)polymorphic assumed-rank arrays
correctly.


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (14 preceding siblings ...)
  2012-10-03 17:32 ` burnus at gcc dot gnu.org
@ 2012-10-16 13:02 ` burnus at gcc dot gnu.org
  2012-10-16 13:13 ` burnus at gcc dot gnu.org
                   ` (4 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-16 13:02 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #16 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-10-16 13:02:09 UTC ---
Author: burnus
Date: Tue Oct 16 13:02:02 2012
New Revision: 192495

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=192495
Log:
2012-10-16  Tobias Burnus  <burnus@net-b.de>

        PR fortran/50981
        PR fortran/54618
        * trans.h (gfc_conv_derived_to_class, gfc_conv_class_to_class):
        Update prototype.
        * trans-stmt.c (trans_associate_var,gfc_trans_allocate): Update
        calls to those functions.
        * trans-expr.c (gfc_conv_derived_to_class,
        * gfc_conv_class_to_class,
        gfc_conv_expr_present): Handle absent polymorphic arguments.
        (class_scalar_coarray_to_class): New function.
        (gfc_conv_procedure_call): Update calls.

2012-10-16  Tobias Burnus  <burnus@net-b.de>

        PR fortran/50981
        PR fortran/54618
        * gfortran.dg/class_optional_1.f90: New.
        * gfortran.dg/class_optional_2.f90: New.


Added:
    trunk/gcc/testsuite/gfortran.dg/class_optional_1.f90
    trunk/gcc/testsuite/gfortran.dg/class_optional_2.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-expr.c
    trunk/gcc/fortran/trans-stmt.c
    trunk/gcc/fortran/trans.h
    trunk/gcc/testsuite/ChangeLog


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (15 preceding siblings ...)
  2012-10-16 13:02 ` burnus at gcc dot gnu.org
@ 2012-10-16 13:13 ` burnus at gcc dot gnu.org
  2013-04-05  9:32 ` sfilippone at uniroma2 dot it
                   ` (3 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-16 13:13 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #17 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-10-16 13:13:41 UTC ---
Now fixed: Several issues with OPTIONAL.

TODO:
- Issues with OPTIONAL and ELEMENTAL,
  cf. commented FIXME lines in gfortran.dg/class_optional_2.f90
- Support packing of (non)polymorphic assumed-rank/assumed-shape arrays
  (-> CONTIGUOUS; cf. gfortran.dg/class_optional_2.f90)
- Fix INTENT(OUT) handling for allocatable polymorphic arrays (cf. comment 0)
- Analyse the old issue related to class_array_7.f03 (comment 11, comment 12)


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (16 preceding siblings ...)
  2012-10-16 13:13 ` burnus at gcc dot gnu.org
@ 2013-04-05  9:32 ` sfilippone at uniroma2 dot it
  2013-04-05  9:33 ` sfilippone at uniroma2 dot it
                   ` (2 subsequent siblings)
  20 siblings, 0 replies; 22+ messages in thread
From: sfilippone at uniroma2 dot it @ 2013-04-05  9:32 UTC (permalink / raw)
  To: gcc-bugs


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

Salvatore Filippone <sfilippone at uniroma2 dot it> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |sfilippone at uniroma2 dot
                   |                            |it

--- Comment #18 from Salvatore Filippone <sfilippone at uniroma2 dot it> 2013-04-05 09:32:25 UTC ---
(In reply to comment #17)
Hi,
I am seeing intermittent issues with CLASS,ALLOCATABLE,INTENT(OUT) variables
that have a CLASS,ALLOCATABLE component; however when I tried to reduce to the
following test code, it segfaults on the inner clone, whereas the full code
only fails on the outer code. In any case, the attached code is supposed to
work, and it fails  (under 4.7.2, 4.8.0 and trunk)
===============================================
module base_inner
  type inner 
    integer, allocatable :: iv(:)
  contains
    procedure, pass(val) :: clone => inner_clone
  end type inner

contains
  subroutine inner_clone(val,res)
    class(inner) :: val
    class(inner), allocatable, intent(out) :: res

    allocate(inner :: res)
    res%iv = val%iv
  end subroutine inner_clone
end module base_inner
module base_outer
  use base_inner
  type outer
    class(inner), allocatable :: inn
  contains
    procedure, pass(val) :: clone => outer_clone
  end type outer

contains
  subroutine outer_clone(val,res)
    class(outer) :: val
    class(outer), allocatable, intent(out) :: res

    allocate(outer :: res)
    call val%inn%clone(res%inn)
  end subroutine outer_clone
end module base_outer

program testclass

  use base_outer

  class(inner), allocatable :: inner1, inner2
  class(outer), allocatable :: outer1, outer2

  allocate(inner :: inner1)
  allocate(inner1%iv(3))
  call inner1%clone(inner2)
  write(0,*) allocated(inner1),allocated(inner2)

  allocate(outer :: outer1)
  allocate(inner :: outer1%inn)
  allocate(outer1%inn%iv(3))
  call outer1%clone(outer2)
  write(0,*) allocated(outer1),allocated(outer2)


end program testclass


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (17 preceding siblings ...)
  2013-04-05  9:32 ` sfilippone at uniroma2 dot it
@ 2013-04-05  9:33 ` sfilippone at uniroma2 dot it
  2013-04-05 11:35 ` burnus at gcc dot gnu.org
  2013-04-05 12:29 ` sfilippone at uniroma2 dot it
  20 siblings, 0 replies; 22+ messages in thread
From: sfilippone at uniroma2 dot it @ 2013-04-05  9:33 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #19 from Salvatore Filippone <sfilippone at uniroma2 dot it> 2013-04-05 09:33:18 UTC ---
(In reply to comment #17)
Hi,
I am seeing intermittent issues with CLASS,ALLOCATABLE,INTENT(OUT) variables
that have a CLASS,ALLOCATABLE component; however when I tried to reduce to the
following test code, it segfaults on the inner clone, whereas the full code
only fails on the outer code. In any case, the attached code is supposed to
work, and it fails  (under 4.7.2, 4.8.0 and trunk)
===============================================
module base_inner
  type inner 
    integer, allocatable :: iv(:)
  contains
    procedure, pass(val) :: clone => inner_clone
  end type inner

contains
  subroutine inner_clone(val,res)
    class(inner) :: val
    class(inner), allocatable, intent(out) :: res

    allocate(inner :: res)
    res%iv = val%iv
  end subroutine inner_clone
end module base_inner
module base_outer
  use base_inner
  type outer
    class(inner), allocatable :: inn
  contains
    procedure, pass(val) :: clone => outer_clone
  end type outer

contains
  subroutine outer_clone(val,res)
    class(outer) :: val
    class(outer), allocatable, intent(out) :: res

    allocate(outer :: res)
    call val%inn%clone(res%inn)
  end subroutine outer_clone
end module base_outer

program testclass

  use base_outer

  class(inner), allocatable :: inner1, inner2
  class(outer), allocatable :: outer1, outer2

  allocate(inner :: inner1)
  allocate(inner1%iv(3))
  call inner1%clone(inner2)
  write(0,*) allocated(inner1),allocated(inner2)

  allocate(outer :: outer1)
  allocate(inner :: outer1%inn)
  allocate(outer1%inn%iv(3))
  call outer1%clone(outer2)
  write(0,*) allocated(outer1),allocated(outer2)


end program testclass


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (18 preceding siblings ...)
  2013-04-05  9:33 ` sfilippone at uniroma2 dot it
@ 2013-04-05 11:35 ` burnus at gcc dot gnu.org
  2013-04-05 12:29 ` sfilippone at uniroma2 dot it
  20 siblings, 0 replies; 22+ messages in thread
From: burnus at gcc dot gnu.org @ 2013-04-05 11:35 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #20 from Tobias Burnus <burnus at gcc dot gnu.org> 2013-04-05 11:35:11 UTC ---
(In reply to comment #18)
> I am seeing intermittent issues with CLASS,ALLOCATABLE,INTENT(OUT) variables
> that have a CLASS,ALLOCATABLE component; however when I tried to reduce to the
> following test code, it segfaults on the inner clone, whereas the full code
> only fails on the outer code. In any case, the attached code is supposed to
> work, and it fails  (under 4.7.2, 4.8.0 and trunk)

For the code in comment 18 and comment 19, I get the output
 T T
 T T
using the latest draft patch at
https://userpage.physik.fu-berlin.de/~tburnus/final/  (It doesn't help with
comment 3.) Thus, if you build GCC yourself, that might be a work around.


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

* [Bug fortran/54618] [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE
  2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
                   ` (19 preceding siblings ...)
  2013-04-05 11:35 ` burnus at gcc dot gnu.org
@ 2013-04-05 12:29 ` sfilippone at uniroma2 dot it
  20 siblings, 0 replies; 22+ messages in thread
From: sfilippone at uniroma2 dot it @ 2013-04-05 12:29 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #21 from Salvatore Filippone <sfilippone at uniroma2 dot it> 2013-04-05 12:29:11 UTC ---
(In reply to comment #20)
> (In reply to comment #18)
> > I am seeing intermittent issues with CLASS,ALLOCATABLE,INTENT(OUT) variables
> > that have a CLASS,ALLOCATABLE component; however when I tried to reduce to the
> > following test code, it segfaults on the inner clone, whereas the full code
> > only fails on the outer code. In any case, the attached code is supposed to
> > work, and it fails  (under 4.7.2, 4.8.0 and trunk)
> 
> For the code in comment 18 and comment 19, I get the output
>  T T
>  T T
> using the latest draft patch at
> https://userpage.physik.fu-berlin.de/~tburnus/final/  (It doesn't help with
> comment 3.) Thus, if you build GCC yourself, that might be a work around.

Thanks for the heads up. 
After further reflection, I've come to realize that for what I want to do, I
can use INTENT(OUT) only when FINAL works. So, from now on I can fork a code
with INTENT(OUT) and test your patch, but the main stable code will have to do
with INTENT(INOUT) until FINAL is fully tested.

Thanks a lot


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

end of thread, other threads:[~2013-04-05 12:29 UTC | newest]

Thread overview: 22+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2012-09-18 15:24 [Bug fortran/54618] New: [OOP] wrong-code with CLASS(...), INTENT(OUT) -- and OPTIONAL or ALLOCATABLE burnus at gcc dot gnu.org
2012-09-19  8:18 ` [Bug fortran/54618] " burnus at gcc dot gnu.org
2012-09-19 13:31 ` burnus at gcc dot gnu.org
2012-09-19 17:31 ` burnus at gcc dot gnu.org
2012-09-19 20:18 ` mikael at gcc dot gnu.org
2012-09-22 17:07 ` burnus at gcc dot gnu.org
2012-09-23  6:49 ` burnus at gcc dot gnu.org
2012-09-24 19:05 ` burnus at gcc dot gnu.org
2012-09-25 14:20 ` burnus at gcc dot gnu.org
2012-09-25 18:37 ` burnus at gcc dot gnu.org
2012-09-26  5:51 ` burnus at gcc dot gnu.org
2012-09-30 12:51 ` dominiq at lps dot ens.fr
2012-09-30 17:01 ` burnus at gcc dot gnu.org
2012-09-30 18:02 ` burnus at gcc dot gnu.org
2012-10-03 14:20 ` burnus at gcc dot gnu.org
2012-10-03 17:32 ` burnus at gcc dot gnu.org
2012-10-16 13:02 ` burnus at gcc dot gnu.org
2012-10-16 13:13 ` burnus at gcc dot gnu.org
2013-04-05  9:32 ` sfilippone at uniroma2 dot it
2013-04-05  9:33 ` sfilippone at uniroma2 dot it
2013-04-05 11:35 ` burnus at gcc dot gnu.org
2013-04-05 12:29 ` sfilippone at uniroma2 dot it

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