public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
@ 2012-12-15 23:52 Janus Weil
  2012-12-16 11:40 ` Tobias Burnus
  0 siblings, 1 reply; 9+ messages in thread
From: Janus Weil @ 2012-12-15 23:52 UTC (permalink / raw)
  To: gfortran, gcc-patches

[-- Attachment #1: Type: text/plain, Size: 622 bytes --]

Hi all,

here is a patch for a pretty bad wrong-code regression, which affects
all maintained releases of gfortran. For discussion see bugzilla.

Regtested on x86_64-unknown-linux-gnu. Ok for 4.6, 4.7 and trunk?

Cheers,
Janus



2012-12-15  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.


2012-12-15  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.

[-- Attachment #2: pr55072_v4.diff --]
[-- Type: application/octet-stream, Size: 2697 bytes --]

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 
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" } }
 

[-- Attachment #3: internal_pack_13.f90 --]
[-- Type: application/octet-stream, Size: 557 bytes --]

! { dg-do run }
!
! PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
!
! Contributed by Tobias Burnus <burnus@gcc.gnu.org>

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

[-- Attachment #4: internal_pack_14.f90 --]
[-- Type: application/octet-stream, Size: 606 bytes --]

! { dg-do run }
!
! PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
!
! Contributed by Janus Weil <janus@gcc.gnu.org>

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
    if (any (k(1:2)%ID /= [1, 1])) call abort()
  end subroutine

end

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-12-15 23:52 [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type Janus Weil
@ 2012-12-16 11:40 ` Tobias Burnus
  2012-12-16 13:03   ` Janus Weil
  0 siblings, 1 reply; 9+ messages in thread
From: Tobias Burnus @ 2012-12-16 11:40 UTC (permalink / raw)
  To: Janus Weil; +Cc: gfortran, gcc-patches

Janus Weil wrote:
> here is a patch for a pretty bad wrong-code regression, which affects
> all maintained releases of gfortran. For discussion see bugzilla.
>
> 2012-12-15  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.
>
> @@ -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)

Without experimenting more carefully, I have the gut feeling that there 
are still cases where we might end up with invalid code and there is 
missed optimization.


Regarding the latter: If the variable is simply contiguous, there is no 
need to pack it. Hence, for

type(t), allocatable :: a(:)
...
call bar(a)

there is no need to pack the array. The problem with the original test 
case is that one has a non-CONTIGUOUS pointer:

p => tgt(::2,::2)
call bar(p)

But that has in principle nothing to do with BT_DERIVED. In particular, 
I would like to see an additional test case for the first example case 
with "ptr" having the CONTIGUOUS attribute - and a check that then no 
packing call is invoked.


For the second test case (comment 2, from GiBUU): Here, the problem is 
that "full_array_var" is wrongly true:

   call s1(OutPart(1,:))


I wonder whether some call to gfc_is_simply_contiguous could solve the 
problem for both issues.

(For non-whole arrays one still have to ensure that one passes the 
correct element: "call(a)" should pass a->data and not "&a" and "call 
bar(a(:,2))" should neither pass "a->data" nor "&a" but "a->data + offset".)

Regarding BT_CLASS: BT_CLASS -> BT_TYPE (with same declared type) should 
already be handled via gfc_conv_subref_array_arg, which takes care of 
the actual type. Thus, the patched function should only be reachable for 
BT_CLASS -> BT_CLASS. Here, packing is required for non-simply 
contiguous actual arguments; but after the packing, a class container 
has to be re-added. I think one should add a test case for this; testing 
declared type == actual type and declared type != actual type - and 
either one for both declared type being the same and for the dummy 
having the declared type of the ancestor of the declared type of the 
actual argument. And all cases for both simply contiguous arrays and 
(simply - or better actually) noncontiguous arrays.

Regarding the wrong code: I fear that some code involving non-BT_DERIVED 
could lead to wrong code, e.g. "a(:)%x". I don't have an example for 
that but I fear that code which lead to the original issue (e.g. 
"full_array_var" is true although it shouldn't) is not solved via the patch.


Sorry for listing more my concerns that giving a proper review.

Tobias

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-12-16 11:40 ` Tobias Burnus
@ 2012-12-16 13:03   ` Janus Weil
  2013-01-10 19:39     ` Janus Weil
  0 siblings, 1 reply; 9+ messages in thread
From: Janus Weil @ 2012-12-16 13:03 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gfortran, gcc-patches

Hi Tobias,

>> here is a patch for a pretty bad wrong-code regression, which affects
>> all maintained releases of gfortran. For discussion see bugzilla.
>>
>> 2012-12-15  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.
>>
>> @@ -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)
>
> Without experimenting more carefully, I have the gut feeling that there are
> still cases where we might end up with invalid code and there is missed
> optimization.
>
> Regarding the latter: If the variable is simply contiguous, there is no need
> to pack it. Hence, for
>
> type(t), allocatable :: a(:)
> ...
> call bar(a)
>
> there is no need to pack the array.

Hm, ok. Do we do any packing in this case? Anyway, this sort of
missed-optimization issue can be treated in a follow-up patch, I
guess. (Mikael also noted a similar missed-optimization case in
comment #13 of the PR.)

What I'm aiming for here is primarily a patch for the wrong-code
regression which is suitable for all three maintained branches.


> The problem with the original test case
> is that one has a non-CONTIGUOUS pointer:
>
> p => tgt(::2,::2)
> call bar(p)
>
> But that has in principle nothing to do with BT_DERIVED.

Yes, the reason for the patch to handle BT_DERIVED in particular, is
that the original commit which introduced the regression (i.e.
r156749) messed up things for BT_DERIVED, which is what I'm reverting.


> In particular, I
> would like to see an additional test case for the first example case with
> "ptr" having the CONTIGUOUS attribute - and a check that then no packing
> call is invoked.

I just checked this: The patched trunk seems to handle this properly
and does not do any packing.

However, I think there might be another problem:

implicit none
type t
  integer :: i
end type t
type(t), target :: tgt(4,4)
type(t), pointer, contiguous :: p(:,:)
p => tgt(::2,::2)        ! accepts invalid?
end

The pointer assignment of a contiguous pointer to a non-contiguous
target should probably be rejected, right? Another follow-up problem
...


> For the second test case (comment 2, from GiBUU): Here, the problem is that
> "full_array_var" is wrongly true:
>
>   call s1(OutPart(1,:))
>
> I wonder whether some call to gfc_is_simply_contiguous could solve the
> problem for both issues.

No, here I disagree. The problem with this one was not related to the
call of "s1", but of "s2", where indeed a full array is passed!



> (For non-whole arrays one still have to ensure that one passes the correct
> element: "call(a)" should pass a->data and not "&a" and "call bar(a(:,2))"
> should neither pass "a->data" nor "&a" but "a->data + offset".)
>
> Regarding BT_CLASS: BT_CLASS -> BT_TYPE (with same declared type) should
> already be handled via gfc_conv_subref_array_arg, which takes care of the
> actual type. Thus, the patched function should only be reachable for
> BT_CLASS -> BT_CLASS. Here, packing is required for non-simply contiguous
> actual arguments; but after the packing, a class container has to be
> re-added. I think one should add a test case for this; testing declared type
> == actual type and declared type != actual type - and either one for both
> declared type being the same and for the dummy having the declared type of
> the ancestor of the declared type of the actual argument. And all cases for
> both simply contiguous arrays and (simply - or better actually)
> noncontiguous arrays.

I'm ignoring all this for now. All I want to fix at this point is the
wrong-code regression!


> Regarding the wrong code: I fear that some code involving non-BT_DERIVED
> could lead to wrong code, e.g. "a(:)%x". I don't have an example for that

If you find an example where stuff goes wrong (as a regression of my
patch), I'll take care of it.


> but I fear that code which lead to the original issue (e.g. "full_array_var"
> is true although it shouldn't) is not solved via the patch.

I actually don't think this is the case!


> Sorry for listing more my concerns that giving a proper review.

Thanks for your comments, anyway.

Cheers,
Janus

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2012-12-16 13:03   ` Janus Weil
@ 2013-01-10 19:39     ` Janus Weil
  2013-01-11 17:19       ` Mikael Morin
  0 siblings, 1 reply; 9+ messages in thread
From: Janus Weil @ 2013-01-10 19:39 UTC (permalink / raw)
  To: Tobias Burnus; +Cc: gfortran, gcc-patches, Paul Thomas

Ping! (What do we do with this little bugger?)

@Paul: Was your comment 19 in the PR meant as an OK for my patch
(submitted here: http://gcc.gnu.org/ml/fortran/2012-12/msg00097.html),
or was it just a general agreement with the previous comments?

Cheers,
Janus



2012/12/16 Janus Weil <janus@gcc.gnu.org>:
> Hi Tobias,
>
>>> here is a patch for a pretty bad wrong-code regression, which affects
>>> all maintained releases of gfortran. For discussion see bugzilla.
>>>
>>> 2012-12-15  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.
>>>
>>> @@ -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)
>>
>> Without experimenting more carefully, I have the gut feeling that there are
>> still cases where we might end up with invalid code and there is missed
>> optimization.
>>
>> Regarding the latter: If the variable is simply contiguous, there is no need
>> to pack it. Hence, for
>>
>> type(t), allocatable :: a(:)
>> ...
>> call bar(a)
>>
>> there is no need to pack the array.
>
> Hm, ok. Do we do any packing in this case? Anyway, this sort of
> missed-optimization issue can be treated in a follow-up patch, I
> guess. (Mikael also noted a similar missed-optimization case in
> comment #13 of the PR.)
>
> What I'm aiming for here is primarily a patch for the wrong-code
> regression which is suitable for all three maintained branches.
>
>
>> The problem with the original test case
>> is that one has a non-CONTIGUOUS pointer:
>>
>> p => tgt(::2,::2)
>> call bar(p)
>>
>> But that has in principle nothing to do with BT_DERIVED.
>
> Yes, the reason for the patch to handle BT_DERIVED in particular, is
> that the original commit which introduced the regression (i.e.
> r156749) messed up things for BT_DERIVED, which is what I'm reverting.
>
>
>> In particular, I
>> would like to see an additional test case for the first example case with
>> "ptr" having the CONTIGUOUS attribute - and a check that then no packing
>> call is invoked.
>
> I just checked this: The patched trunk seems to handle this properly
> and does not do any packing.
>
> However, I think there might be another problem:
>
> implicit none
> type t
>   integer :: i
> end type t
> type(t), target :: tgt(4,4)
> type(t), pointer, contiguous :: p(:,:)
> p => tgt(::2,::2)        ! accepts invalid?
> end
>
> The pointer assignment of a contiguous pointer to a non-contiguous
> target should probably be rejected, right? Another follow-up problem
> ...
>
>
>> For the second test case (comment 2, from GiBUU): Here, the problem is that
>> "full_array_var" is wrongly true:
>>
>>   call s1(OutPart(1,:))
>>
>> I wonder whether some call to gfc_is_simply_contiguous could solve the
>> problem for both issues.
>
> No, here I disagree. The problem with this one was not related to the
> call of "s1", but of "s2", where indeed a full array is passed!
>
>
>
>> (For non-whole arrays one still have to ensure that one passes the correct
>> element: "call(a)" should pass a->data and not "&a" and "call bar(a(:,2))"
>> should neither pass "a->data" nor "&a" but "a->data + offset".)
>>
>> Regarding BT_CLASS: BT_CLASS -> BT_TYPE (with same declared type) should
>> already be handled via gfc_conv_subref_array_arg, which takes care of the
>> actual type. Thus, the patched function should only be reachable for
>> BT_CLASS -> BT_CLASS. Here, packing is required for non-simply contiguous
>> actual arguments; but after the packing, a class container has to be
>> re-added. I think one should add a test case for this; testing declared type
>> == actual type and declared type != actual type - and either one for both
>> declared type being the same and for the dummy having the declared type of
>> the ancestor of the declared type of the actual argument. And all cases for
>> both simply contiguous arrays and (simply - or better actually)
>> noncontiguous arrays.
>
> I'm ignoring all this for now. All I want to fix at this point is the
> wrong-code regression!
>
>
>> Regarding the wrong code: I fear that some code involving non-BT_DERIVED
>> could lead to wrong code, e.g. "a(:)%x". I don't have an example for that
>
> If you find an example where stuff goes wrong (as a regression of my
> patch), I'll take care of it.
>
>
>> but I fear that code which lead to the original issue (e.g. "full_array_var"
>> is true although it shouldn't) is not solved via the patch.
>
> I actually don't think this is the case!
>
>
>> Sorry for listing more my concerns that giving a proper review.
>
> Thanks for your comments, anyway.
>
> Cheers,
> Janus

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2013-01-10 19:39     ` Janus Weil
@ 2013-01-11 17:19       ` Mikael Morin
  2013-01-11 20:32         ` Janus Weil
  0 siblings, 1 reply; 9+ messages in thread
From: Mikael Morin @ 2013-01-11 17:19 UTC (permalink / raw)
  To: Janus Weil; +Cc: Tobias Burnus, gfortran, gcc-patches, Paul Thomas

Le 10/01/2013 20:39, Janus Weil a écrit :
> Ping! (What do we do with this little bugger?)
>
> @Paul: Was your comment 19 in the PR meant as an OK for my patch
> (submitted here: http://gcc.gnu.org/ml/fortran/2012-12/msg00097.html),
> or was it just a general agreement with the previous comments?
>
FWIW, I regard the patch as a (conservative) improvement, thus certainly 
acceptable.

For:
 >>> @@ -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)

I would have used instead:
  && expr->expr_type == EXPR_VARIABLE && ref == NULL)

to make the optimization available to variables of derived type.
As we are now in stage4, your version should probably be preferred though.


Regarding:
>>>
>>> Regarding the wrong code: I fear that some code involving non-BT_DERIVED
>>> could lead to wrong code, e.g. "a(:)%x". I don't have an example for that
>>
I don't think this can happen as the test for non-derived type is on the 
root symbol (`a' in your example).  For other cases, to be honest, I 
can't make any sense of all the booleans interacting with each other in 
that code area (this_array_result, g77, contiguous vs. 
gfc_is_simply_contiguous, ...).

Regarding the missed optimization, bah, maybe we can defer to 4.9+?

Mikael

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2013-01-11 17:19       ` Mikael Morin
@ 2013-01-11 20:32         ` Janus Weil
  2013-01-11 20:51           ` Mikael Morin
  0 siblings, 1 reply; 9+ messages in thread
From: Janus Weil @ 2013-01-11 20:32 UTC (permalink / raw)
  To: Mikael Morin; +Cc: Tobias Burnus, gfortran, gcc-patches, Paul Thomas

Hi Mikael,

>> Ping! (What do we do with this little bugger?)
>>
>> @Paul: Was your comment 19 in the PR meant as an OK for my patch
>> (submitted here: http://gcc.gnu.org/ml/fortran/2012-12/msg00097.html),
>> or was it just a general agreement with the previous comments?
>>
> FWIW, I regard the patch as a (conservative) improvement, thus certainly
> acceptable.

To be conservative was exactly my intention, since
a) trunk is in stage 4 and
b) I wanted something that is safe for backporting to 4.6 and 4.7
(where we certainly can not afford to introduce any new wrong-code
regressions).


>>>> @@ -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)
>
> I would have used instead:
>  && expr->expr_type == EXPR_VARIABLE && ref == NULL)
>
> to make the optimization available to variables of derived type.
> As we are now in stage4, your version should probably be preferred though.

Ok, I will leave it as it is then.


> Regarding:
>
>>>> Regarding the wrong code: I fear that some code involving non-BT_DERIVED
>>>> could lead to wrong code, e.g. "a(:)%x". I don't have an example for
>>>> that
>>>
> I don't think this can happen as the test for non-derived type is on the
> root symbol (`a' in your example).  For other cases, to be honest, I can't
> make any sense of all the booleans interacting with each other in that code
> area (this_array_result, g77, contiguous vs. gfc_is_simply_contiguous, ...).
>
> Regarding the missed optimization, bah, maybe we can defer to 4.9+?

Yes, certainly the upcoming release should better produce code that is
fully correct, rather than "fast but wrong" ;)


Thanks for your review (which I read as an OK for all branches,
right?). Will commit soon.

Cheers,
Janus

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2013-01-11 20:32         ` Janus Weil
@ 2013-01-11 20:51           ` Mikael Morin
  2013-01-11 22:25             ` Paul Richard Thomas
  0 siblings, 1 reply; 9+ messages in thread
From: Mikael Morin @ 2013-01-11 20:51 UTC (permalink / raw)
  To: Janus Weil; +Cc: Tobias Burnus, gfortran, gcc-patches, Paul Thomas

Le 11/01/2013 21:31, Janus Weil a écrit :
> Thanks for your review (which I read as an OK for all branches,
> right?).
>
Well, from my point of view it is OK, but I was actually hoping Tobias 
would ack it himself.

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2013-01-11 20:51           ` Mikael Morin
@ 2013-01-11 22:25             ` Paul Richard Thomas
  2013-01-12 19:01               ` Janus Weil
  0 siblings, 1 reply; 9+ messages in thread
From: Paul Richard Thomas @ 2013-01-11 22:25 UTC (permalink / raw)
  To: Mikael Morin; +Cc: Janus Weil, Tobias Burnus, gfortran, gcc-patches

To be clear - I was awaiting a formal submission but indicating that I
would OK it when it was made.  I completely missed the posting of 16th
December.

OK by me for trunk, followed by 4.6 and 4.7.

Cheers

Paul

On 11 January 2013 21:51, Mikael Morin <mikael.morin@sfr.fr> wrote:
> Le 11/01/2013 21:31, Janus Weil a écrit :
>
>> Thanks for your review (which I read as an OK for all branches,
>> right?).
>>
> Well, from my point of view it is OK, but I was actually hoping Tobias would
> ack it himself.



-- 
The knack of flying is learning how to throw yourself at the ground and miss.
       --Hitchhikers Guide to the Galaxy

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

* Re: [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type
  2013-01-11 22:25             ` Paul Richard Thomas
@ 2013-01-12 19:01               ` Janus Weil
  0 siblings, 0 replies; 9+ messages in thread
From: Janus Weil @ 2013-01-12 19:01 UTC (permalink / raw)
  To: Paul Richard Thomas; +Cc: Mikael Morin, Tobias Burnus, gfortran, gcc-patches

> OK by me for trunk, followed by 4.6 and 4.7.

Thanks, Paul. Committed to trunk as r195125. Will do the branches soon.

Cheers,
Janus




> On 11 January 2013 21:51, Mikael Morin <mikael.morin@sfr.fr> wrote:
>> Le 11/01/2013 21:31, Janus Weil a écrit :
>>
>>> Thanks for your review (which I read as an OK for all branches,
>>> right?).
>>>
>> Well, from my point of view it is OK, but I was actually hoping Tobias would
>> ack it himself.
>
>
>
> --
> The knack of flying is learning how to throw yourself at the ground and miss.
>        --Hitchhikers Guide to the Galaxy

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

end of thread, other threads:[~2013-01-12 19:01 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2012-12-15 23:52 [Patch, Fortran] PR 55072: [4.6/4.7/4.8 Regression] Missing internal_pack leads to wrong code with derived type Janus Weil
2012-12-16 11:40 ` Tobias Burnus
2012-12-16 13:03   ` Janus Weil
2013-01-10 19:39     ` Janus Weil
2013-01-11 17:19       ` Mikael Morin
2013-01-11 20:32         ` Janus Weil
2013-01-11 20:51           ` Mikael Morin
2013-01-11 22:25             ` Paul Richard Thomas
2013-01-12 19:01               ` Janus Weil

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