public inbox for gcc-bugs@sourceware.org
help / color / mirror / Atom feed
* [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
@ 2012-10-25  9:22 burnus at gcc dot gnu.org
  2012-10-25  9:30 ` [Bug fortran/55072] " burnus at gcc dot gnu.org
                   ` (23 more replies)
  0 siblings, 24 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-25  9:22 UTC (permalink / raw)
  To: gcc-bugs


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

             Bug #: 55072
           Summary: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack
                    leads to wrong code with derived type
    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


The following code should print (and does so with GCC 4.1, 4.3 and 4.4):
           1           9           3          11
           1           9           3          11
However, starting from GCC 4.5, it prints:
           1           9           3          11
           1           5           9          13

The reason is that the passed pointer is not packed but directly passed (with
array descriptor, which is not used):

  bar ((struct t[0:] *) p.data);

while gfortran 4.4 correctly uses:

    D.1575 = _gfortran_internal_pack (&p);
    bar (D.1575);


implicit none
type t
integer :: i
end type t
type(t), target :: tgt(4,4)
type(t), pointer :: p(:,:)
integer :: i,j,k

k = 1
do i = 1, 4
  do j = 1, 4
    tgt(i,j)%i = k
    k = k+1
  end do
end do

p => tgt(::2,::2)
print *,p%i
call bar(p)

contains

  subroutine bar(x)
    type(t) :: x(*)
    print *,x(1:4)%i
    if (any (x(1:4)%i /= [1, 9, 3, 11])) call abort()
  end subroutine
end


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

* [Bug fortran/55072] [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
@ 2012-10-25  9:30 ` burnus at gcc dot gnu.org
  2012-11-07 10:35 ` [Bug fortran/55072] [4.6/4.7/4.8 " jakub at gcc dot gnu.org
                   ` (22 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: burnus at gcc dot gnu.org @ 2012-10-25  9:30 UTC (permalink / raw)
  To: gcc-bugs


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

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

           What    |Removed                     |Added
----------------------------------------------------------------------------
                 CC|                            |burnus at gcc dot gnu.org,
                   |                            |janus at gcc dot gnu.org,
                   |                            |pault at gcc dot gnu.org
   Target Milestone|---                         |4.6.4

--- Comment #1 from Tobias Burnus <burnus at gcc dot gnu.org> 2012-10-25 09:30:30 UTC ---
The issue seems to be the following in trans-array.c's
gfc_conv_array_parameter:

  ultimate_ptr_comp = false;
...
  for (ref = expr->ref; ref; ref = ref->next)
    {
      if (ref->next == NULL)
        break;

      if (ref->type == REF_COMPONENT)
        {
          ultimate_ptr_comp = ref->u.c.component->attr.pointer;
          ultimate_alloc_comp = ref->u.c.component->attr.allocatable;
        }
    }
...
  if (expr->expr_type == EXPR_VARIABLE && ref && !ultimate_ptr_comp)
    full_array_var = gfc_full_array_ref_p (ref, &contiguous);

where "ref" is:
(gdb) p expr->ref->type 
$6 = REF_ARRAY
(gdb) p expr->ref->u.ar.type 
$7 = AR_FULL



Possibly patch. I think it needs some audit whether ultimate_alloc_comp  has to
be handled as well and whether other BT_CLASS updates are required as well
further down.

--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -6957,6 +6957,11 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr,
bool g77,
   ultimate_ptr_comp = false;
   ultimate_alloc_comp = false;

+  if (expr->symtree)
+    ultimate_ptr_comp = expr->symtree->n.sym->ts.type == BT_CLASS
+                       ? CLASS_DATA (expr->symtree->n.sym)->attr.class_pointer
+                       : expr->symtree->n.sym->attr.pointer;
+
   for (ref = expr->ref; ref; ref = ref->next)
     {
       if (ref->next == NULL)


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
  2012-10-25  9:30 ` [Bug fortran/55072] " burnus at gcc dot gnu.org
@ 2012-11-07 10:35 ` jakub at gcc dot gnu.org
  2012-12-13 21:39 ` janus at gcc dot gnu.org
                   ` (21 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: jakub at gcc dot gnu.org @ 2012-11-07 10:35 UTC (permalink / raw)
  To: gcc-bugs


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

Jakub Jelinek <jakub at gcc dot gnu.org> changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
           Priority|P3                          |P4
                 CC|                            |jakub at gcc dot gnu.org


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
  2012-10-25  9:30 ` [Bug fortran/55072] " burnus at gcc dot gnu.org
  2012-11-07 10:35 ` [Bug fortran/55072] [4.6/4.7/4.8 " jakub at gcc dot gnu.org
@ 2012-12-13 21:39 ` janus at gcc dot gnu.org
  2012-12-13 22:20 ` dominiq at lps dot ens.fr
                   ` (20 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-13 21:39 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|UNCONFIRMED                 |NEW
   Last reconfirmed|                            |2012-12-13
     Ever Confirmed|0                           |1

--- Comment #2 from janus at gcc dot gnu.org 2012-12-13 21:39:29 UTC ---
It seems I found yet another reincarnation of this bug (spotted in the wild,
unfortunately):


program GiBUU_neutrino_bug

  Type particle
    integer :: ID
  End Type

  type(particle), dimension(1:2,1:2) :: OutPart

  OutPart(1,:)%ID = 1
  OutPart(2,:)%ID = 2

  call s1(OutPart(1,:))

contains

  subroutine s1(j)
    type(particle) :: j(:)
    print *,j(:)%ID
    call s2(j)
  end subroutine

  subroutine s2(k)
    type(particle) :: k(1:2)
    print *,k(:)%ID
  end subroutine

end


It is expected to print
           1           1
           1           1
which it does with 4.3 and 4.4. As the test case in comment 0, it fails with
everything from 4.5 up to trunk, printing:
           1           1
           1           2
A workaround is to declare both 'i' and 'j' in the same way, as either (:) or
(1:2).


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (2 preceding siblings ...)
  2012-12-13 21:39 ` janus at gcc dot gnu.org
@ 2012-12-13 22:20 ` dominiq at lps dot ens.fr
  2012-12-13 23:04 ` janus at gcc dot gnu.org
                   ` (19 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: dominiq at lps dot ens.fr @ 2012-12-13 22:20 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #3 from Dominique d'Humieres <dominiq at lps dot ens.fr> 2012-12-13 22:20:25 UTC ---
Revision 156618 (2010-02-09) is OK.
Revision 157955 (2010-03-30) miscompiles the tests.


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (3 preceding siblings ...)
  2012-12-13 22:20 ` dominiq at lps dot ens.fr
@ 2012-12-13 23:04 ` janus at gcc dot gnu.org
  2012-12-14 23:18 ` janus at gcc dot gnu.org
                   ` (18 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-13 23:04 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #4 from janus at gcc dot gnu.org 2012-12-13 23:04:15 UTC ---
(In reply to comment #2)
> It seems I found yet another reincarnation of this bug (spotted in the wild,
> unfortunately):

Note: The patch in comment #1 does not seem to fix the behavior in comment #2.

So, either the patch is not complete, or comment #2 is a distinct problem after
all. (I would say that it's at least loosely related, even though I do not
completely understand the problem yet.)


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (4 preceding siblings ...)
  2012-12-13 23:04 ` janus at gcc dot gnu.org
@ 2012-12-14 23:18 ` janus at gcc dot gnu.org
  2012-12-14 23:19 ` janus at gcc dot gnu.org
                   ` (17 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-14 23:18 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #5 from janus at gcc dot gnu.org 2012-12-14 23:17:01 UTC ---
Some debugging of comment #2:

With old versions of gfortran (e.g. 4.3), the argument in the call to s2 is
being packed:

    D.938 = _gfortran_internal_pack (&parm.8);
    s2 (D.938);

With newer versions (e.g. trunk), this is not the case any more:

    s2 ((struct particle[0:] *) parm.8.data);


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (5 preceding siblings ...)
  2012-12-14 23:18 ` janus at gcc dot gnu.org
@ 2012-12-14 23:19 ` janus at gcc dot gnu.org
  2012-12-15  0:19 ` janus at gcc dot gnu.org
                   ` (16 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-14 23:19 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #6 from janus at gcc dot gnu.org 2012-12-14 23:18:13 UTC ---
(In reply to comment #3)
> Revision 156618 (2010-02-09) is OK.
> Revision 157955 (2010-03-30) miscompiles the tests.

Taking a guess:

http://gcc.gnu.org/viewcvs?view=revision&revision=156749


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (6 preceding siblings ...)
  2012-12-14 23:19 ` janus at gcc dot gnu.org
@ 2012-12-15  0:19 ` janus at gcc dot gnu.org
  2012-12-15 10:56 ` janus at gcc dot gnu.org
                   ` (15 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15  0:19 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #7 from janus at gcc dot gnu.org 2012-12-15 00:18:58 UTC ---
The following patch (which amounts to a partial revert of r156749) fixes the
behavior of comment #2 for me:


Index: gcc/fortran/trans-array.c
===================================================================
--- gcc/fortran/trans-array.c    (revision 194387)
+++ gcc/fortran/trans-array.c    (working copy)
@@ -6957,6 +6957,11 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr *
   ultimate_ptr_comp = false;
   ultimate_alloc_comp = false;

+  if (expr->symtree)
+    ultimate_ptr_comp = expr->symtree->n.sym->ts.type == BT_CLASS
+            ? CLASS_DATA (expr->symtree->n.sym)->attr.class_pointer
+            : expr->symtree->n.sym->attr.pointer;
+
   for (ref = expr->ref; ref; ref = ref->next)
     {
       if (ref->next == NULL)


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (7 preceding siblings ...)
  2012-12-15  0:19 ` janus at gcc dot gnu.org
@ 2012-12-15 10:56 ` janus at gcc dot gnu.org
  2012-12-15 11:00 ` janus at gcc dot gnu.org
                   ` (14 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 10:56 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #8 from janus at gcc dot gnu.org 2012-12-15 10:56:26 UTC ---
(In reply to comment #7)
> The following patch (which amounts to a partial revert of r156749) fixes the
> behavior of comment #2 for me:

Note: The patch in comment #7 actually fixes both test cases (comment #0 and
#2), and is in that sense superior over the patch in comment #1.

However, it yields the following testsuite failures:

FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
"sub_array_assumed \\(D" 2
FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
"\\.data = \\(void .\\) &array_t1.0.;" 1
FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
"sub_array_assumed \\(\\(struct t1.0:. .\\) parm" 1
FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
"sub_array_assumed \\(\\(struct t3.0:. .\\) array_t3_ptr.data\\);" 1

FAIL: gfortran.dg/internal_pack_10.f90  -O0  execution test


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (8 preceding siblings ...)
  2012-12-15 10:56 ` janus at gcc dot gnu.org
@ 2012-12-15 11:00 ` janus at gcc dot gnu.org
  2012-12-15 13:06 ` janus at gcc dot gnu.org
                   ` (13 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 11:00 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #9 from janus at gcc dot gnu.org 2012-12-15 11:00:09 UTC ---
(In reply to comment #7)
> The following patch (which amounts to a partial revert of r156749) fixes the
> behavior of comment #2 for me:


Ugh. Apparently it was much too late last night, when I accidentally re-posted
the patch of comment #1 instead of the one I actually wanted to post:


Index: gcc/fortran/trans-array.c
===================================================================
--- gcc/fortran/trans-array.c    (revision 194387)
+++ gcc/fortran/trans-array.c    (working copy)
@@ -7002,13 +7002,6 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr *
       if (sym->ts.type == BT_CHARACTER)
     se->string_length = sym->ts.u.cl->backend_decl;

-      if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
-    {
-      gfc_conv_expr_descriptor (se, expr);
-      se->expr = gfc_conv_array_data (se->expr);
-      return;
-    }
-
       if (!sym->attr.pointer
       && sym->as
       && sym->as->type != AS_ASSUMED_SHAPE 


This is the patch that both comment 7 and comment 8 refer to.


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (9 preceding siblings ...)
  2012-12-15 11:00 ` janus at gcc dot gnu.org
@ 2012-12-15 13:06 ` janus at gcc dot gnu.org
  2012-12-15 13:46 ` janus at gcc dot gnu.org
                   ` (12 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 13:06 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #10 from janus at gcc dot gnu.org 2012-12-15 13:06:37 UTC ---
Here is a reduced version of internal_pack_10.f90, which is the only
runtime-failure in the testsuite for the patch in comment #9:

module mo_obs_rules
  type t_set
     integer :: use = 0
  end type
  type t_rules
     character(len=10) :: comment
     type(t_set)       :: c (1)
  end type
contains
  subroutine set_set_v (src)
    type(t_set), intent(in)    :: src(1)
    if (any (src%use .ne. 99)) call abort
  end subroutine
end module

program test
  use mo_obs_rules
  type (t_rules) :: ru (1)
  ru(1)%c(:)%use = 99
  call set_set_v (ru(1)%c)
end program


The problem is that, without the patch, an array descriptor is generated for
the argument to 'set_set_v':

    parm.3.data = (void *) &ru[0].c[0];
    parm.3.offset = -1;
    set_set_v ((struct t_set[0:] *) parm.3.data);

which is not the case with the patch:

  set_set_v (&ru);


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (10 preceding siblings ...)
  2012-12-15 13:06 ` janus at gcc dot gnu.org
@ 2012-12-15 13:46 ` janus at gcc dot gnu.org
  2012-12-15 16:05 ` janus at gcc dot gnu.org
                   ` (11 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 13:46 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #11 from janus at gcc dot gnu.org 2012-12-15 13:46:26 UTC ---
Ok, revised version of the patch from comment 9, which fixes the runtime
failure on internal_pack_10.f90:


Index: gcc/fortran/trans-array.c
===================================================================
--- gcc/fortran/trans-array.c    (revision 194517)
+++ gcc/fortran/trans-array.c    (working copy)
@@ -6995,20 +6995,14 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr *
     this_array_result = false;

   /* Passing address of the array if it is not pointer or assumed-shape.  */
-  if (full_array_var && g77 && !this_array_result)
+  if (full_array_var && g77 && !this_array_result
+      && sym->ts.type != BT_DERIVED && sym->ts.type != BT_CLASS)
     {
       tmp = gfc_get_symbol_decl (sym);

       if (sym->ts.type == BT_CHARACTER)
     se->string_length = sym->ts.u.cl->backend_decl;

-      if (sym->ts.type == BT_DERIVED || sym->ts.type == BT_CLASS)
-    {
-      gfc_conv_expr_descriptor (se, expr);
-      se->expr = gfc_conv_array_data (se->expr);
-      return;
-    }
-
       if (!sym->attr.pointer
       && sym->as
       && sym->as->type != AS_ASSUMED_SHAPE 



Note: This still shows scan-tree-dump failures on assumed_type_2.f90, but now
only 2 of them at -O0 (instead of 4):

FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
"sub_array_assumed \\(D" 2
FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
"sub_array_assumed \\(\\(struct t3.0:. .\\) array_t3_ptr.data\\);" 1

Will do another full regtest ...


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (11 preceding siblings ...)
  2012-12-15 13:46 ` janus at gcc dot gnu.org
@ 2012-12-15 16:05 ` janus at gcc dot gnu.org
  2012-12-15 16:17 ` mikael at gcc dot gnu.org
                   ` (10 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 16:05 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #12 from janus at gcc dot gnu.org 2012-12-15 16:05:36 UTC ---
(In reply to comment #11)
> Note: This still shows scan-tree-dump failures on assumed_type_2.f90, but now
> only 2 of them at -O0 (instead of 4):
> 
> FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
> "sub_array_assumed \\(D" 2
> FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
> "sub_array_assumed \\(\\(struct t3.0:. .\\) array_t3_ptr.data\\);" 1
> 
> Will do another full regtest ...


Ok, I have verified that those two are indeed the only testsuite failures of
the patch in comment #11.


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (12 preceding siblings ...)
  2012-12-15 16:05 ` janus at gcc dot gnu.org
@ 2012-12-15 16:17 ` mikael at gcc dot gnu.org
  2012-12-15 19:46 ` janus at gcc dot gnu.org
                   ` (9 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: mikael at gcc dot gnu.org @ 2012-12-15 16:17 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #13 from Mikael Morin <mikael at gcc dot gnu.org> 2012-12-15 16:16:57 UTC ---
(In reply to comment #10)
> Here is a reduced version of internal_pack_10.f90, which is the only
> runtime-failure in the testsuite for the patch in comment #9:
> 
[...]
>   call set_set_v (ru(1)%c)
> end program
> 
> 
> The problem is that, without the patch, an array descriptor is generated for
> the argument to 'set_set_v':
> 
>     parm.3.data = (void *) &ru[0].c[0];
>     parm.3.offset = -1;
>     set_set_v ((struct t_set[0:] *) parm.3.data);
> 
> which is not the case with the patch:
> 
>   set_set_v (&ru);

Well, it seems that an array descriptor isn't even necessary. But the
non-descriptor case should look like:

set_set_v (&(ru[0].c[0]));



(In reply to comment #11)
> Ok, revised version of the patch from comment 9, which fixes the runtime
> failure on internal_pack_10.f90:
> 
> 
> Index: gcc/fortran/trans-array.c
> ===================================================================
> --- gcc/fortran/trans-array.c    (revision 194517)
> +++ gcc/fortran/trans-array.c    (working copy)
> @@ -6995,20 +6995,14 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr *
>      this_array_result = false;
> 
>    /* Passing address of the array if it is not pointer or assumed-shape.  */
> -  if (full_array_var && g77 && !this_array_result)
> +  if (full_array_var && g77 && !this_array_result
> +      && sym->ts.type != BT_DERIVED && sym->ts.type != BT_CLASS)
>      {
>        tmp = gfc_get_symbol_decl (sym);
> 
It feels like a hack (that what there before) to blindly disable derived types
here.  The real problem is that the code under the if condition supports only
bare variables without subreferences.
On the other hand it looks like a correct hack WRT the existing behaviour.


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (13 preceding siblings ...)
  2012-12-15 16:17 ` mikael at gcc dot gnu.org
@ 2012-12-15 19:46 ` janus at gcc dot gnu.org
  2012-12-15 20:47 ` janus at gcc dot gnu.org
                   ` (8 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 19:46 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #14 from janus at gcc dot gnu.org 2012-12-15 19:46:37 UTC ---
(In reply to comment #13)
> (In reply to comment #11)
> > Ok, revised version of the patch from comment 9, which fixes the runtime
> > failure on internal_pack_10.f90:
> > 
> > [...]
> > 
> It feels like a hack (that what there before) to blindly disable derived types
> here.  The real problem is that the code under the if condition supports only
> bare variables without subreferences.
> On the other hand it looks like a correct hack WRT the existing behaviour.

Well, yeah. My primary concern right now is really to get the regression fixed
ASAP (this sort of wrong-code regression is pretty much the worst thing which
can happen in terms of compiler bugs, I guess).

But of course you're right about the underlying problem. If you are willing to
fix this, it would be greatly appreciated. (I currently do not have the
capacities to take care of it, unfortunately.)


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (14 preceding siblings ...)
  2012-12-15 19:46 ` janus at gcc dot gnu.org
@ 2012-12-15 20:47 ` janus at gcc dot gnu.org
  2012-12-15 21:06 ` janus at gcc dot gnu.org
                   ` (7 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 20:47 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #15 from janus at gcc dot gnu.org 2012-12-15 20:47:00 UTC ---
(In reply to comment #11)
> FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
> "sub_array_assumed \\(D" 2
> FAIL: gfortran.dg/assumed_type_2.f90  -O0   scan-tree-dump-times original
> "sub_array_assumed \\(\\(struct t3.0:. .\\) array_t3_ptr.data\\);" 1


Here is a reduced test case for these two failure (which are apparently due to
a single underlying problem):


! { dg-do compile }
! { dg-options "-fdump-tree-original" }

implicit none
type :: t3
  integer :: c
end type t3

type(t3), pointer     :: array_t3_ptr(:,:)

call sub_array_assumed (array_t3_ptr)

contains

  subroutine sub_array_assumed (arg3)
     type(*), target :: arg3(*)
  end subroutine

end

! { dg-final { scan-tree-dump-times "sub_array_assumed \\(D" 0 "original" } }
! { dg-final { scan-tree-dump-times "sub_array_assumed \\(\\(struct t3.0:. .\\)
array_t3_ptr.data\\);" 1 "original" } }
! { dg-final { cleanup-tree-dump "original" } }


The point is this: Without the patch, the subroutine call is translated to:

  sub_array_assumed ((struct t3[0:] *) array_t3_ptr.data);

while, with the patch, it becomes:

    D.1892 = _gfortran_internal_pack (&array_t3_ptr);
    sub_array_assumed (D.1892);

i.e., the argument is packed.


Question is: Is the packing needed here? I would guess that it isn't. And if
not, how do we best avoid it?


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (15 preceding siblings ...)
  2012-12-15 20:47 ` janus at gcc dot gnu.org
@ 2012-12-15 21:06 ` janus at gcc dot gnu.org
  2012-12-15 21:26 ` janus at gcc dot gnu.org
                   ` (6 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 21:06 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #16 from janus at gcc dot gnu.org 2012-12-15 21:06:11 UTC ---
(In reply to comment #15)
> 
> type(t3), pointer     :: array_t3_ptr(:,:)
> 
> call sub_array_assumed (array_t3_ptr)
> 
> contains
> 
>   subroutine sub_array_assumed (arg3)
>      type(*), target :: arg3(*)
>   end subroutine
> 
> end
> 
> [...]
> 
> Question is: Is the packing needed here? I would guess that it isn't.

Of course I might be wrong here. After all, array_t3_ptr is a pointer, so it's
not guaranteed to be contiguous, right?

If the packing is indeed required in this place, we just need to fix the test
case (assumed_type_2.f90) ...


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (16 preceding siblings ...)
  2012-12-15 21:06 ` janus at gcc dot gnu.org
@ 2012-12-15 21:26 ` janus at gcc dot gnu.org
  2012-12-15 23:41 ` janus at gcc dot gnu.org
                   ` (5 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 21:26 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #17 from janus at gcc dot gnu.org 2012-12-15 21:26:32 UTC ---
(In reply to comment #16)
> > Question is: Is the packing needed here? I would guess that it isn't.
> 
> Of course I might be wrong here. After all, array_t3_ptr is a pointer, so it's
> not guaranteed to be contiguous, right?

To answer that myself, I think the packing is indeed needed here. At least it
is also done for similar cases in the same test case, such as this one:

character, pointer :: array_char_ptr(:,:)
call sub_array_assumed (array_char_ptr)


> If the packing is indeed required in this place, we just need to fix the test
> case (assumed_type_2.f90) ...

... like this:


Index: gcc/testsuite/gfortran.dg/assumed_type_2.f90
===================================================================
--- gcc/testsuite/gfortran.dg/assumed_type_2.f90    (revision 194517)
+++ gcc/testsuite/gfortran.dg/assumed_type_2.f90    (working copy)
@@ -157,7 +157,7 @@ end
 ! { dg-final { scan-tree-dump-times "sub_scalar .\\(struct t1 .\\)
array_class_t1_alloc._data.data" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "sub_scalar .\\(struct t1 .\\)
array_class_t1_ptr._data.dat" 1 "original" } }a

-! { dg-final { scan-tree-dump-times "sub_array_assumed \\(D" 2 "original" } }
+! { dg-final { scan-tree-dump-times "sub_array_assumed \\(D" 3 "original" } }
 ! { dg-final { scan-tree-dump-times " = _gfortran_internal_pack \\(&parm" 1
"original" } }
 ! { dg-final { scan-tree-dump-times "sub_array_assumed \\(&array_int\\)" 1
"original" } }
 ! { dg-final { scan-tree-dump-times "sub_array_assumed
\\(\\(real\\(kind=4\\).0:. . restrict\\) array_real_alloc.data" 1 "original" }
}
@@ -165,7 +165,6 @@ end
 ! { dg-final { scan-tree-dump-times "\\.data = \\(void .\\) &array_t1.0.;" 1
"original" } }
 ! { dg-final { scan-tree-dump-times "sub_array_assumed \\(\\(struct t1.0:.
.\\) parm" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "sub_array_assumed \\(\\(struct t2.0:. .
restrict\\) array_t2_alloc.data\\);" 1 "original" } }
-! { dg-final { scan-tree-dump-times "sub_array_assumed \\(\\(struct t3.0:.
.\\) array_t3_ptr.data\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "sub_array_assumed \\(\\(struct t1.0:. .
restrict\\) array_class_t1_alloc._data.data\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "sub_array_assumed \\(\\(struct t1.0:.
.\\) array_class_t1_ptr._data.data\\);" 1 "original" } }


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (17 preceding siblings ...)
  2012-12-15 21:26 ` janus at gcc dot gnu.org
@ 2012-12-15 23:41 ` janus at gcc dot gnu.org
  2013-01-09 13:17 ` pault at gcc dot gnu.org
                   ` (4 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2012-12-15 23:41 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|NEW                         |ASSIGNED
         AssignedTo|unassigned at gcc dot       |janus at gcc dot gnu.org
                   |gnu.org                     |

--- Comment #18 from janus at gcc dot gnu.org 2012-12-15 23:40:43 UTC ---
(In reply to comment #17)
> (In reply to comment #16)
> > > Question is: Is the packing needed here? I would guess that it isn't.
> > 
> > Of course I might be wrong here. After all, array_t3_ptr is a pointer, so it's
> > not guaranteed to be contiguous, right?
> 
> To answer that myself, I think the packing is indeed needed here.

In fact this is exactly the case of comment 0. So, yes, we definitely need the
packing!


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (18 preceding siblings ...)
  2012-12-15 23:41 ` janus at gcc dot gnu.org
@ 2013-01-09 13:17 ` pault at gcc dot gnu.org
  2013-01-12 18:52 ` janus at gcc dot gnu.org
                   ` (3 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: pault at gcc dot gnu.org @ 2013-01-09 13:17 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #19 from Paul Thomas <pault at gcc dot gnu.org> 2013-01-09 13:16:59 UTC ---
(In reply to comment #18)
> (In reply to comment #17)
> > (In reply to comment #16)
> > > > Question is: Is the packing needed here? I would guess that it isn't.
> > > 
> > > Of course I might be wrong here. After all, array_t3_ptr is a pointer, so it's
> > > not guaranteed to be contiguous, right?
> > 
> > To answer that myself, I think the packing is indeed needed here.
> In fact this is exactly the case of comment 0. So, yes, we definitely need the
> packing!

Dear Janus,

R156749 was clearly an optimization too far. As far as correct code generation
is concerned, you cannot have too many PACKs.  Therefore, I would apply your
regression fix, even if you are worried that it over-does it.

Cheers

Paul


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (19 preceding siblings ...)
  2013-01-09 13:17 ` pault at gcc dot gnu.org
@ 2013-01-12 18:52 ` janus at gcc dot gnu.org
  2013-01-13 12:06 ` janus at gcc dot gnu.org
                   ` (2 subsequent siblings)
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-12 18:52 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #20 from janus at gcc dot gnu.org 2013-01-12 18:52:18 UTC ---
Author: janus
Date: Sat Jan 12 18:52:11 2013
New Revision: 195125

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=195125
Log:
2013-01-12  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/55072
    * trans-array.c (gfc_conv_array_parameter): No packing was done for
    full arrays of derived type.


2013-01-12  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/55072
    * gfortran.dg/assumed_type_2.f90: Fix test case.
    * gfortran.dg/internal_pack_13.f90: New test.
    * gfortran.dg/internal_pack_14.f90: New test.

Added:
    trunk/gcc/testsuite/gfortran.dg/internal_pack_13.f90
    trunk/gcc/testsuite/gfortran.dg/internal_pack_14.f90
Modified:
    trunk/gcc/fortran/ChangeLog
    trunk/gcc/fortran/trans-array.c
    trunk/gcc/testsuite/ChangeLog
    trunk/gcc/testsuite/gfortran.dg/assumed_type_2.f90


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (20 preceding siblings ...)
  2013-01-12 18:52 ` janus at gcc dot gnu.org
@ 2013-01-13 12:06 ` janus at gcc dot gnu.org
  2013-01-14 21:25 ` janus at gcc dot gnu.org
  2013-01-14 21:45 ` janus at gcc dot gnu.org
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-13 12:06 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #21 from janus at gcc dot gnu.org 2013-01-13 12:06:10 UTC ---
Author: janus
Date: Sun Jan 13 12:06:04 2013
New Revision: 195135

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=195135
Log:
2013-01-13  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/55072
    * trans-array.c (gfc_conv_array_parameter): No packing was done for
    full arrays of derived type.


2013-01-13  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/55072
    * gfortran.dg/internal_pack_13.f90: New test.
    * gfortran.dg/internal_pack_14.f90: New test.

Added:
    branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/internal_pack_13.f90
    branches/gcc-4_7-branch/gcc/testsuite/gfortran.dg/internal_pack_14.f90
Modified:
    branches/gcc-4_7-branch/gcc/fortran/ChangeLog
    branches/gcc-4_7-branch/gcc/fortran/trans-array.c
    branches/gcc-4_7-branch/gcc/testsuite/ChangeLog


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (21 preceding siblings ...)
  2013-01-13 12:06 ` janus at gcc dot gnu.org
@ 2013-01-14 21:25 ` janus at gcc dot gnu.org
  2013-01-14 21:45 ` janus at gcc dot gnu.org
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-14 21:25 UTC (permalink / raw)
  To: gcc-bugs


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

--- Comment #22 from janus at gcc dot gnu.org 2013-01-14 21:24:43 UTC ---
Author: janus
Date: Mon Jan 14 21:24:36 2013
New Revision: 195178

URL: http://gcc.gnu.org/viewcvs?root=gcc&view=rev&rev=195178
Log:
2013-01-14  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/55072
    * trans-array.c (gfc_conv_array_parameter): No packing was done for
    full arrays of derived type.


2013-01-14  Janus Weil  <janus@gcc.gnu.org>

    PR fortran/55072
    * gfortran.dg/internal_pack_13.f90: New test.
    * gfortran.dg/internal_pack_14.f90: New test.

Added:
    branches/gcc-4_6-branch/gcc/testsuite/gfortran.dg/internal_pack_13.f90
    branches/gcc-4_6-branch/gcc/testsuite/gfortran.dg/internal_pack_14.f90
Modified:
    branches/gcc-4_6-branch/gcc/fortran/ChangeLog
    branches/gcc-4_6-branch/gcc/fortran/trans-array.c
    branches/gcc-4_6-branch/gcc/testsuite/ChangeLog


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

* [Bug fortran/55072] [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
                   ` (22 preceding siblings ...)
  2013-01-14 21:25 ` janus at gcc dot gnu.org
@ 2013-01-14 21:45 ` janus at gcc dot gnu.org
  23 siblings, 0 replies; 25+ messages in thread
From: janus at gcc dot gnu.org @ 2013-01-14 21:45 UTC (permalink / raw)
  To: gcc-bugs


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

janus at gcc dot gnu.org changed:

           What    |Removed                     |Added
----------------------------------------------------------------------------
             Status|ASSIGNED                    |RESOLVED
         Resolution|                            |FIXED

--- Comment #23 from janus at gcc dot gnu.org 2013-01-14 21:45:17 UTC ---
The wrong-code regression has been fixed on all branches (4.6, 4.7 and trunk).

For all remaining problems (missed optimizations etc), I have opened PR 55980.

Closing this one as fixed.


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

end of thread, other threads:[~2013-01-14 21:45 UTC | newest]

Thread overview: 25+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2012-10-25  9:22 [Bug fortran/55072] New: [4.5/4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type burnus at gcc dot gnu.org
2012-10-25  9:30 ` [Bug fortran/55072] " burnus at gcc dot gnu.org
2012-11-07 10:35 ` [Bug fortran/55072] [4.6/4.7/4.8 " jakub at gcc dot gnu.org
2012-12-13 21:39 ` janus at gcc dot gnu.org
2012-12-13 22:20 ` dominiq at lps dot ens.fr
2012-12-13 23:04 ` janus at gcc dot gnu.org
2012-12-14 23:18 ` janus at gcc dot gnu.org
2012-12-14 23:19 ` janus at gcc dot gnu.org
2012-12-15  0:19 ` janus at gcc dot gnu.org
2012-12-15 10:56 ` janus at gcc dot gnu.org
2012-12-15 11:00 ` janus at gcc dot gnu.org
2012-12-15 13:06 ` janus at gcc dot gnu.org
2012-12-15 13:46 ` janus at gcc dot gnu.org
2012-12-15 16:05 ` janus at gcc dot gnu.org
2012-12-15 16:17 ` mikael at gcc dot gnu.org
2012-12-15 19:46 ` janus at gcc dot gnu.org
2012-12-15 20:47 ` janus at gcc dot gnu.org
2012-12-15 21:06 ` janus at gcc dot gnu.org
2012-12-15 21:26 ` janus at gcc dot gnu.org
2012-12-15 23:41 ` janus at gcc dot gnu.org
2013-01-09 13:17 ` pault at gcc dot gnu.org
2013-01-12 18:52 ` janus at gcc dot gnu.org
2013-01-13 12:06 ` janus at gcc dot gnu.org
2013-01-14 21:25 ` janus at gcc dot gnu.org
2013-01-14 21:45 ` janus 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).