public inbox for gcc-patches@gcc.gnu.org
 help / color / mirror / Atom feed
* [Patch, Fortran] Simplify lbound
@ 2015-04-25 11:34 Thomas Koenig
  2015-04-25 18:13 ` Mikael Morin
  0 siblings, 1 reply; 14+ messages in thread
From: Thomas Koenig @ 2015-04-25 11:34 UTC (permalink / raw)
  To: fortran, gcc-patches

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

Hello world,

this is a simplification for calculating the lboud of assumed-shape
arrays - it is usually one, or whatever the user specified as
lower bound (if constant).

The surprising thing was that the current code generated for the
array descriptor for

  subroutine foo(a, b, n, m)
    integer, dimension(:), intent(inout) :: a
    integer, dimension(-2:), intent(inout) :: b
    integer, intent(out) :: n,m
    n = lbound(a,1)
    m = lbound(b,1)
  end subroutine foo

was not simplified to the simple assignment even at -O.  This is
what the assembly looks like with the patch:

        movl    $1, (%rdx)
        movl    $-2, (%rcx)
        ret

and this is what it looks like without the patch:

        movq    24(%rsi), %rax
        testq   %rax, %rax
        movl    $1, %edi
        cmove   %rdi, %rax
        movq    40(%rsi), %rdi
        subq    32(%rsi), %rdi
        movq    %rdi, %rsi
        subq    $2, %rsi
        movl    $1, (%rdx)
        movq    %rax, %rdx
        notq    %rdx
        shrq    $63, %rdx
        cmpq    $-2, %rsi
        setge   %sil
        movzbl  %sil, %esi
        testl   %edx, %esi
        jne     .L6
        shrq    $63, %rax
        movl    $1, %edx
        testl   %eax, %eax
        je      .L3
.L6:
        movl    $-2, %edx
.L3:
        movl    %edx, (%rcx)
        ret

This is important for the matmul inline patch, because I am using
lbound extensively there.  The other cases (allocatables and
pointers as dummy arguments) are already covered.

Regression-tested.  OK for trunk?


2015-04-25  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/37131
	* simplify.c (simplify_bound): Get constant lower bounds
	from array spec for assumed shape arrays.

2015-04-25  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/37131
	* gfortran.dg/coarray_lib_this_image_2.f90:  Adjust
	scan pattern.
	* gfortran.dg/bound_9.f90:  New test case.

[-- Attachment #2: p2.diff --]
[-- Type: text/x-patch, Size: 2381 bytes --]

Index: fortran/simplify.c
===================================================================
--- fortran/simplify.c	(Revision 222431)
+++ fortran/simplify.c	(Arbeitskopie)
@@ -3445,6 +3445,32 @@ simplify_bound (gfc_expr *array, gfc_expr *dim, gf
 
  done:
 
+
+  if (!upper && as && as->type == AS_ASSUMED_SHAPE && dim
+      && dim->expr_type == EXPR_CONSTANT && ref->u.ar.type != AR_SECTION)
+    {
+      if (!(array->symtree && array->symtree->n.sym
+	    && (array->symtree->n.sym->attr.allocatable
+		|| array->symtree->n.sym->attr.pointer)))
+	{
+	  unsigned long int ndim;
+	  gfc_expr *lower, *res;
+
+	  ndim = mpz_get_si (dim->value.integer) - 1;
+	  lower = as->lower[ndim];
+	  if (lower->expr_type == EXPR_CONSTANT)
+	    {
+	      res = gfc_copy_expr (lower);
+	      if (kind)
+		{
+		  int nkind = mpz_get_si (kind->value.integer);
+		  res->ts.kind = nkind;
+		}
+	      return res;
+	    }
+	}
+    }
+
   if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
 	     || as->type == AS_ASSUMED_RANK))
     return NULL;
Index: testsuite/gfortran.dg/coarray_lib_this_image_2.f90
===================================================================
--- testsuite/gfortran.dg/coarray_lib_this_image_2.f90	(Revision 222431)
+++ testsuite/gfortran.dg/coarray_lib_this_image_2.f90	(Arbeitskopie)
@@ -20,7 +20,7 @@ end
 ! { dg-final { scan-tree-dump-times "mylcobound = 5;" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "parm...dim\\\[1\\\].lbound = 5;" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "myucobound =\[^\n\r\]* parm...dim\\\[1\\\].lbound \\+ \[^\n\r\]*_gfortran_caf_num_images \\(0, -1\\).? \\+ -?\[0-9\]+\\);" 1 "original" } }
-! { dg-final { scan-tree-dump-times "mylbound = parm...dim\\\[0\\\].stride >= 0 && parm...dim\\\[0\\\].ubound >= parm...dim\\\[0\\\].lbound \\|\\| parm...dim\\\[0\\\].stride < 0 \\?\[^\n\r\]* parm...dim\\\[0\\\].lbound : 1;" 1 "original" } }
+! { dg-final { scan-tree-dump-times "mylbound = 1;" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "mythis_image = _gfortran_caf_this_image \\(0\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "bar \\(&parm.\[0-9\]+, caf_token.\[0-9\]+, \\(integer\\(kind=\[48\]\\)\\) parm.\[0-9\]+.data - \\(integer\\(kind=\[48\]\\)\\) x\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "_gfortran_caf_init \\(&argc, &argv\\);" 1 "original" } }

[-- Attachment #3: bound_9.f90 --]
[-- Type: text/x-fortran, Size: 855 bytes --]

! { dg-do  run }
! Check that simplificiation of ubound is done.
! { dg-options "-O -fdump-tree-original -fdump-tree-optimized" }
module bar
  implicit none
contains
  subroutine foo(a, b, n, m)
    integer, dimension(:), intent(inout) :: a
    integer, dimension(-2:), intent(inout) :: b
    integer, intent(out) :: n,m
    n = lbound(a,1)
    m = lbound(b,1)
  end subroutine foo
end module bar

program main
  use bar
  implicit none
  integer, dimension(3) :: a, b
  integer :: n,m

  call foo(a,b,n,m)
  if (n .ne. 1 .or. m .ne. -2) call abort
end program main
! { dg-final { scan-tree-dump-times "\\*n = 1" 1 "original" } }
! { dg-final { scan-tree-dump-times "\\*m = -2" 1 "original" } }
! { dg-final { scan-tree-dump-times "lbound" 0 "optimized" } }
! { dg-final { cleanup-tree-dump "original" } }
! { dg-final { cleanup-tree-dump "optimized" } }

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

* Re: [Patch, Fortran] Simplify lbound
  2015-04-25 11:34 [Patch, Fortran] Simplify lbound Thomas Koenig
@ 2015-04-25 18:13 ` Mikael Morin
  2015-04-27 18:45   ` Thomas Koenig
  0 siblings, 1 reply; 14+ messages in thread
From: Mikael Morin @ 2015-04-25 18:13 UTC (permalink / raw)
  To: Thomas Koenig, fortran, gcc-patches

Le 25/04/2015 13:33, Thomas Koenig a écrit :
> Hello world,
> 
> this is a simplification for calculating the lboud of assumed-shape
> arrays - it is usually one, or whatever the user specified as
> lower bound (if constant).
> 
Hello,

I've double-checked in the standard, and it seems it is not possible to
simplify after all:

	If ARRAY is a whole array and either ARRAY is an assumed-size
	array of rank DIM or dimension DIM of ARRAY has nonzero extent,
	LBOUND (ARRAY, DIM) has a value equal to the lower bound for
	subscript DIM of ARRAY. Otherwise the result value is 1.

We can't tell whether the array is zero-sized, so we can't tell the
lbound value.


As you may want to simplify in the limited scope of the matmul inlining,
I'm giving comments about the patch (otherwise you can ignore them):
 - No need to check for allocatable or pointer, it should be excluded by
as->type == AS_ASSUMED_SHAPE (but does no harm either).
 - Please modify the early return condition:
     if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
	        || as->type == AS_ASSUMED_RANK))
       return NULL;
   and let the existing code do the simplification work.


Or drop the lbound simplification idea, and fetch the lbound "by hand"
at matmul inline time.

Mikael

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

* Re: [Patch, Fortran] Simplify lbound
  2015-04-25 18:13 ` Mikael Morin
@ 2015-04-27 18:45   ` Thomas Koenig
  2015-04-27 19:22     ` Thomas Koenig
                       ` (2 more replies)
  0 siblings, 3 replies; 14+ messages in thread
From: Thomas Koenig @ 2015-04-27 18:45 UTC (permalink / raw)
  To: Mikael Morin, fortran, gcc-patches

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

Am 25.04.2015 um 20:12 schrieb Mikael Morin:

> I've double-checked in the standard, and it seems it is not possible to
> simplify after all:
> 
> 	If ARRAY is a whole array and either ARRAY is an assumed-size
> 	array of rank DIM or dimension DIM of ARRAY has nonzero extent,
> 	LBOUND (ARRAY, DIM) has a value equal to the lower bound for
> 	subscript DIM of ARRAY. Otherwise the result value is 1.
> 
> We can't tell whether the array is zero-sized, so we can't tell the
> lbound value.

So it is only possible to simplify LBOUND if the lower bound is
equal to one, both for assumed-shape and explicit-shape arrays...
OK.

The attached patch does that, including a test case which catches
that particular case.

> As you may want to simplify in the limited scope of the matmul inlining,
> I'm giving comments about the patch (otherwise you can ignore them):
>  - No need to check for allocatable or pointer, it should be excluded by
> as->type == AS_ASSUMED_SHAPE (but does no harm either).

Actually, no.  You can have assumed-shape allocatable or pointer
dummy arguments which keep their original lbound; see the subroutine
'bar' in the test case.

>  - Please modify the early return condition:
>      if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
> 	        || as->type == AS_ASSUMED_RANK))
>        return NULL;
>    and let the existing code do the simplification work.

That is not part of my patch.

> Or drop the lbound simplification idea, and fetch the lbound "by hand"
> at matmul inline time.

I will probably do so as a future optimization, but I think that most
people will see no reason for using different lower bounds, so it is
OK for the time being to (slightly) pessimize this case.

So... here is the new patch.  OK for trunk?

	Thomas

2015-04-25  Thomas Koenig  <tkoenig@gcc.gnu.org>

        PR fortran/37131
        * simplify.c (simplify_bound): Get constant lower bounds of one
        from array spec for assumed and explicit shape shape arrays if
        the lower bounds are indeed one.

2015-04-25  Thomas Koenig  <tkoenig@gcc.gnu.org>

        PR fortran/37131
        * gfortran.dg/coarray_lib_this_image_2.f90:  Adjust
        scan pattern.
        * gfortran.dg/bound_9.f90:  New test case.

P.S:

In an earlier version, I also added

Index: trans-array.c
===================================================================
--- trans-array.c       (Revision 222431)
+++ trans-array.c       (Arbeitskopie)
@@ -5693,6 +5693,7 @@ gfc_trans_array_bounds (tree type, gfc_symbol * sy
             to being zero size.  */
          tmp = fold_build2_loc (input_location, GE_EXPR, boolean_type_node,
                                 stride, gfc_index_zero_node);
+         tmp = gfc_likely (tmp, PRED_FORTRAN_SIZE_ZERO);
          tmp = fold_build3_loc (input_location, COND_EXPR,
                                 gfc_array_index_type, tmp,
                                 stride, gfc_index_zero_node);

but that caused the condition to always return true.  I haven't figured
out why, but either I am misunderstanding something here, or gfc_likely
is buggy, or both.


[-- Attachment #2: p4.diff --]
[-- Type: text/x-patch, Size: 1437 bytes --]

Index: simplify.c
===================================================================
--- simplify.c	(Revision 222431)
+++ simplify.c	(Arbeitskopie)
@@ -3445,6 +3445,39 @@ simplify_bound (gfc_expr *array, gfc_expr *dim, gf
 
  done:
 
+  /* If the array shape is assumed shape or explicit, we can simplify lbound
+     to 1 if the given lower bound is one because this matches what lbound
+     should return for an empty array.  */
+
+  if (!upper && as && dim && dim->expr_type == EXPR_CONSTANT
+      && (as->type == AS_ASSUMED_SHAPE || as->type == AS_EXPLICIT) 
+      && ref->u.ar.type != AR_SECTION)
+    {
+      /* Watch out for allocatable or pointer dummy arrays, they can have
+	 lower bounds that are not equal to one.  */
+      if (!(array->symtree && array->symtree->n.sym
+	    && (array->symtree->n.sym->attr.allocatable
+		|| array->symtree->n.sym->attr.pointer)))
+	{
+	  unsigned long int ndim;
+	  gfc_expr *lower, *res;
+
+	  ndim = mpz_get_si (dim->value.integer) - 1;
+	  lower = as->lower[ndim];
+	  if (lower->expr_type == EXPR_CONSTANT
+	      && mpz_cmp_si (lower->value.integer, 1) == 0)
+	    {
+	      res = gfc_copy_expr (lower);
+	      if (kind)
+		{
+		  int nkind = mpz_get_si (kind->value.integer);
+		  res->ts.kind = nkind;
+		}
+	      return res;
+	    }
+	}
+    }
+
   if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
 	     || as->type == AS_ASSUMED_RANK))
     return NULL;

[-- Attachment #3: bound_9.f90 --]
[-- Type: text/x-fortran, Size: 1837 bytes --]

! { dg-do  run }
! { dg-options "-fdump-tree-original" }
! Check for different combinations of lbound for dummy arrays,
! stressing empty arrays.  The assignments with "one =" should
! be simplified at compile time.
module tst
  implicit none
contains
  subroutine foo (a, b, one, m)
    integer, dimension(:), intent(in) :: a
    integer, dimension (-2:), intent(in) :: b
    integer, intent(out) :: one, m
    one = lbound(a,1)
    m = lbound(b,1)
  end subroutine foo

  subroutine bar (a, b, n, m)
    integer, dimension(:), allocatable, intent(inout) :: a
    integer, dimension(:), pointer, intent(inout) :: b
    integer, intent(out) :: n, m
    n = lbound(a,1)
    m = lbound(b,1)
  end subroutine bar

  subroutine baz (a, n, m, s)
    integer, intent(in) :: n,m
    integer, intent(out) :: s
    integer, dimension(n:m) :: a
    s = lbound(a,1)
  end subroutine baz

  subroutine qux (a, s, one)
    integer, intent(in) :: s
    integer, dimension(s) :: a
    integer, intent(out) :: one
    one = lbound(a,1)
  end subroutine qux
end module tst

program main
  use tst
  implicit none
  integer, dimension(3), target :: a, b
  integer, dimension(0) :: empty
  integer, dimension(:), allocatable :: x
  integer, dimension(:), pointer :: y
  integer :: n,m
  

  call foo(a,b,n,m)
  if (n .ne. 1 .or. m .ne. -2) call abort
  call foo(a(2:0), empty, n, m)
  if (n .ne. 1 .or. m .ne. 1) call abort
  call foo(empty, a(2:0), n, m)
  if (n .ne. 1 .or. m .ne. 1) call abort
  allocate (x(0))
  call bar (x, y, n, m)
  if (n .ne. 1 .or. m .ne. 1) call abort

  call baz(a,3,2,n)
  if (n .ne. 1) call abort

  call baz(a,2,3,n)
  if (n .ne. 2) call abort

  call qux(a, -3, n)
  if (n .ne. 1) call abort
end program main
! { dg-final { scan-tree-dump-times "\\*one = 1" 2 "original" } }
! { dg-final { cleanup-tree-dump "original" } }

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

* Re: [Patch, Fortran] Simplify lbound
  2015-04-27 18:45   ` Thomas Koenig
@ 2015-04-27 19:22     ` Thomas Koenig
  2015-04-30 18:46     ` Mikael Morin
  2015-05-02 10:50     ` H.J. Lu
  2 siblings, 0 replies; 14+ messages in thread
From: Thomas Koenig @ 2015-04-27 19:22 UTC (permalink / raw)
  To: fortran, gcc-patches

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

Hello world,

here is a slight correction: This patch includes the change to
the test case.

Regards

	Thomas



[-- Attachment #2: p4a.diff --]
[-- Type: text/x-patch, Size: 2791 bytes --]

Index: fortran/simplify.c
===================================================================
--- fortran/simplify.c	(Revision 222431)
+++ fortran/simplify.c	(Arbeitskopie)
@@ -3445,6 +3445,39 @@ simplify_bound (gfc_expr *array, gfc_expr *dim, gf
 
  done:
 
+  /* If the array shape is assumed shape or explicit, we can simplify lbound
+     to 1 if the given lower bound is one because this matches what lbound
+     should return for an empty array.  */
+
+  if (!upper && as && dim && dim->expr_type == EXPR_CONSTANT
+      && (as->type == AS_ASSUMED_SHAPE || as->type == AS_EXPLICIT) 
+      && ref->u.ar.type != AR_SECTION)
+    {
+      /* Watch out for allocatable or pointer dummy arrays, they can have
+	 lower bounds that are not equal to one.  */
+      if (!(array->symtree && array->symtree->n.sym
+	    && (array->symtree->n.sym->attr.allocatable
+		|| array->symtree->n.sym->attr.pointer)))
+	{
+	  unsigned long int ndim;
+	  gfc_expr *lower, *res;
+
+	  ndim = mpz_get_si (dim->value.integer) - 1;
+	  lower = as->lower[ndim];
+	  if (lower->expr_type == EXPR_CONSTANT
+	      && mpz_cmp_si (lower->value.integer, 1) == 0)
+	    {
+	      res = gfc_copy_expr (lower);
+	      if (kind)
+		{
+		  int nkind = mpz_get_si (kind->value.integer);
+		  res->ts.kind = nkind;
+		}
+	      return res;
+	    }
+	}
+    }
+
   if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
 	     || as->type == AS_ASSUMED_RANK))
     return NULL;
Index: testsuite/gfortran.dg/coarray_lib_this_image_2.f90
===================================================================
--- testsuite/gfortran.dg/coarray_lib_this_image_2.f90	(Revision 222431)
+++ testsuite/gfortran.dg/coarray_lib_this_image_2.f90	(Arbeitskopie)
@@ -20,7 +20,7 @@ end
 ! { dg-final { scan-tree-dump-times "mylcobound = 5;" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "parm...dim\\\[1\\\].lbound = 5;" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "myucobound =\[^\n\r\]* parm...dim\\\[1\\\].lbound \\+ \[^\n\r\]*_gfortran_caf_num_images \\(0, -1\\).? \\+ -?\[0-9\]+\\);" 1 "original" } }
-! { dg-final { scan-tree-dump-times "mylbound = parm...dim\\\[0\\\].stride >= 0 && parm...dim\\\[0\\\].ubound >= parm...dim\\\[0\\\].lbound \\|\\| parm...dim\\\[0\\\].stride < 0 \\?\[^\n\r\]* parm...dim\\\[0\\\].lbound : 1;" 1 "original" } }
+! { dg-final { scan-tree-dump-times "mylbound = 1;" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "mythis_image = _gfortran_caf_this_image \\(0\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "bar \\(&parm.\[0-9\]+, caf_token.\[0-9\]+, \\(integer\\(kind=\[48\]\\)\\) parm.\[0-9\]+.data - \\(integer\\(kind=\[48\]\\)\\) x\\);" 1 "original" } }
 ! { dg-final { scan-tree-dump-times "_gfortran_caf_init \\(&argc, &argv\\);" 1 "original" } }

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

* Re: [Patch, Fortran] Simplify lbound
  2015-04-27 18:45   ` Thomas Koenig
  2015-04-27 19:22     ` Thomas Koenig
@ 2015-04-30 18:46     ` Mikael Morin
  2015-05-01 21:04       ` Mikael Morin
  2015-05-02 10:50     ` H.J. Lu
  2 siblings, 1 reply; 14+ messages in thread
From: Mikael Morin @ 2015-04-30 18:46 UTC (permalink / raw)
  To: Thomas Koenig, fortran, gcc-patches

Le 27/04/2015 20:45, Thomas Koenig a écrit :
> Am 25.04.2015 um 20:12 schrieb Mikael Morin:
> 
>> I've double-checked in the standard, and it seems it is not possible to
>> simplify after all:
>>
>> 	If ARRAY is a whole array and either ARRAY is an assumed-size
>> 	array of rank DIM or dimension DIM of ARRAY has nonzero extent,
>> 	LBOUND (ARRAY, DIM) has a value equal to the lower bound for
>> 	subscript DIM of ARRAY. Otherwise the result value is 1.
>>
>> We can't tell whether the array is zero-sized, so we can't tell the
>> lbound value.
> 
> So it is only possible to simplify LBOUND if the lower bound is
> equal to one, both for assumed-shape and explicit-shape arrays...
> 
Indeed.

>> As you may want to simplify in the limited scope of the matmul inlining,
>> I'm giving comments about the patch (otherwise you can ignore them):
>>  - No need to check for allocatable or pointer, it should be excluded by
>> as->type == AS_ASSUMED_SHAPE (but does no harm either).
> 
> Actually, no.  You can have assumed-shape allocatable or pointer
> dummy arguments which keep their original lbound; see the subroutine
> 'bar' in the test case.
> 
>>  - Please modify the early return condition:
>>      if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
>> 	        || as->type == AS_ASSUMED_RANK))
>>        return NULL;
>>    and let the existing code do the simplification work.
> 
> That is not part of my patch.
> 
I'm not sure I expressed what I was asking for clearly enough.
Anyway, I may as well submit the requested changes myself.

> So... here is the new patch.  OK for trunk?
> 
Yes, thanks.

Mikael

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

* Re: [Patch, Fortran] Simplify lbound
  2015-04-30 18:46     ` Mikael Morin
@ 2015-05-01 21:04       ` Mikael Morin
  2015-05-03 20:38         ` Thomas Koenig
  0 siblings, 1 reply; 14+ messages in thread
From: Mikael Morin @ 2015-05-01 21:04 UTC (permalink / raw)
  To: Thomas Koenig, fortran, gcc-patches

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

Hello,

Le 30/04/2015 20:19, Mikael Morin a écrit :
>>> As you may want to simplify in the limited scope of the matmul inlining,
>>> I'm giving comments about the patch (otherwise you can ignore them):
>>>  - No need to check for allocatable or pointer, it should be excluded by
>>> as->type == AS_ASSUMED_SHAPE (but does no harm either).
>>
>> Actually, no.  You can have assumed-shape allocatable or pointer
>> dummy arguments which keep their original lbound; see the subroutine
>> 'bar' in the test case.
>>
>>>  - Please modify the early return condition:
>>>      if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
>>> 	        || as->type == AS_ASSUMED_RANK))
>>>        return NULL;
>>>    and let the existing code do the simplification work.
>>
>> That is not part of my patch.
>>
> I'm not sure I expressed what I was asking for clearly enough.
> Anyway, I may as well submit the requested changes myself.
> 
I present here the announced above follow-up change to Thomas' recent
bound simplification patch.

It basically removes the code added and tighten the condition
mentioned above, so that we don't give up too early to simplify the
lbound of an assumed shape array, and let the existing code do the
simplification.

To not regression wrt to Thomas work, I had to also adjust early
give-ups in simplify_bound_dim.
But the code has been reorganized, so that it doesn't appear clearly.
The declared bound and empty bound value have been abstracted
from the differentiated lbound/ubound specifics.  Then the
simplification is applied indifferently on those abstractions.
Finally, the empty array tricks have been disabled for the CO{L,U}BOUND
intrinsics.

With these changes, Thomas' tests continue to work and one gets DIM-less
bound simplification "for free".

The testsuite adds tests for zero sized arrays and DIM-less {L,U}BOUND
calls.
I had to remove the check for absence of string "bound" in the dump:
there is code generated for assumed shape arrays that plays tricks with
bounds and contains that string, even if the code generated for the body
itself of the procedure is empty.

Regression tested on x86_64-unknown-linux-gnu.  OK for trunk?

Mikael





[-- Attachment #2: bound_simplification_integration_full.CL --]
[-- Type: text/plain, Size: 653 bytes --]

2015-05-01  Mikael Morin  <mikael@gcc.gnu.org>

	* simplify.c (simplify_bound_dim): Don't check for emptyness
	in the case of cobound simplification.  Factor lower/upper
	bound differenciation before the actual simplification.
	(simplify_bound): Remove assumed shape specific simplification.  
	Don't give up early for the lbound of an assumed shape.

2015-05-01  Mikael Morin  <mikael@gcc.gnu.org>

	* gfortran.dg/bound_simplification_4.f90: Disable implicit typing.
	Add checks for bound simplification without DIM argument.
	Add checks for empty array and assumed shape bound simplification.
	Remove check for absence of string "bound" in the dump.


[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #3: bound_simplification_integration_full.diff --]
[-- Type: text/x-patch; name="bound_simplification_integration_full.diff", Size: 6476 bytes --]

Index: fortran/simplify.c
===================================================================
--- fortran/simplify.c	(révision 222681)
+++ fortran/simplify.c	(copie de travail)
@@ -3340,29 +3340,43 @@ simplify_bound_dim (gfc_expr *array, gfc_expr *kin
   /* Then, we need to know the extent of the given dimension.  */
   if (coarray || (ref->u.ar.type == AR_FULL && !ref->next))
     {
+      gfc_expr *declared_bound;
+      int empty_bound;
+      bool constant_lbound, constant_ubound;
+
       l = as->lower[d-1];
       u = as->upper[d-1];
 
-      if (l->expr_type != EXPR_CONSTANT || u == NULL
-	  || u->expr_type != EXPR_CONSTANT)
+      gcc_assert (l != NULL);
+
+      constant_lbound = l->expr_type == EXPR_CONSTANT;
+      constant_ubound = u && u->expr_type == EXPR_CONSTANT;
+
+      empty_bound = upper ? 0 : 1;
+      declared_bound = upper ? u : l;
+
+      if ((!upper && !constant_lbound)
+	  || (upper && !constant_ubound))
 	goto returnNull;
 
-      if (mpz_cmp (l->value.integer, u->value.integer) > 0)
+      if (!coarray)
 	{
-	  /* Zero extent.  */
-	  if (upper)
-	    mpz_set_si (result->value.integer, 0);
+	  /* For {L,U}BOUND, the value depends on whether the array
+	     is empty.  We can nevertheless simplify if the declared bound
+	     has the same value as that of an empty array, in which case
+	     the result isn't dependent on the array emptyness.  */
+	  if (mpz_cmp_si (declared_bound->value.integer, empty_bound) == 0)
+	    mpz_set_si (result->value.integer, empty_bound);
+	  else if (!constant_lbound || !constant_ubound)
+	    /* Array emptyness can't be determined, we can't simplify.  */
+	    goto returnNull;
+	  else if (mpz_cmp (l->value.integer, u->value.integer) > 0)
+	    mpz_set_si (result->value.integer, empty_bound);
 	  else
-	    mpz_set_si (result->value.integer, 1);
+	    mpz_set (result->value.integer, declared_bound->value.integer);
 	}
       else
-	{
-	  /* Nonzero extent.  */
-	  if (upper)
-	    mpz_set (result->value.integer, u->value.integer);
-	  else
-	    mpz_set (result->value.integer, l->value.integer);
-	}
+	mpz_set (result->value.integer, declared_bound->value.integer);
     }
   else
     {
@@ -3442,43 +3456,16 @@ simplify_bound (gfc_expr *array, gfc_expr *dim, gf
 
  done:
 
-  /* If the array shape is assumed shape or explicit, we can simplify lbound
-     to 1 if the given lower bound is one because this matches what lbound
-     should return for an empty array.  */
+  if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_RANK
+	     || (as->type == AS_ASSUMED_SHAPE && upper)))
+    return NULL;
 
-  if (!upper && as && dim && dim->expr_type == EXPR_CONSTANT
-      && (as->type == AS_ASSUMED_SHAPE || as->type == AS_EXPLICIT) 
-      && ref->u.ar.type != AR_SECTION)
-    {
-      /* Watch out for allocatable or pointer dummy arrays, they can have
-	 lower bounds that are not equal to one.  */
-      if (!(array->symtree && array->symtree->n.sym
-	    && (array->symtree->n.sym->attr.allocatable
-		|| array->symtree->n.sym->attr.pointer)))
-	{
-	  unsigned long int ndim;
-	  gfc_expr *lower, *res;
+  gcc_assert (!as
+	      || (as->type != AS_DEFERRED
+		  && array->expr_type == EXPR_VARIABLE
+		  && !array->symtree->n.sym->attr.allocatable
+		  && !array->symtree->n.sym->attr.pointer));
 
-	  ndim = mpz_get_si (dim->value.integer) - 1;
-	  lower = as->lower[ndim];
-	  if (lower->expr_type == EXPR_CONSTANT
-	      && mpz_cmp_si (lower->value.integer, 1) == 0)
-	    {
-	      res = gfc_copy_expr (lower);
-	      if (kind)
-		{
-		  int nkind = mpz_get_si (kind->value.integer);
-		  res->ts.kind = nkind;
-		}
-	      return res;
-	    }
-	}
-    }
-
-  if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
-	     || as->type == AS_ASSUMED_RANK))
-    return NULL;
-
   if (dim == NULL)
     {
       /* Multi-dimensional bounds.  */
Index: testsuite/gfortran.dg/bound_simplification_4.f90
===================================================================
--- testsuite/gfortran.dg/bound_simplification_4.f90	(révision 222681)
+++ testsuite/gfortran.dg/bound_simplification_4.f90	(copie de travail)
@@ -3,6 +3,8 @@
 !
 ! Check that {L,U}{,CO}BOUND intrinsics are properly simplified.
 !
+  implicit none
+
   type :: t
     integer :: c
   end type t
@@ -9,11 +11,13 @@
 
   type(t) :: d(3:8) = t(7)
   type(t) :: e[5:9,-1:*]
+  type(t) :: h(3), j(4), k(0)
 
+  !Test full arrays vs subarrays
   if (lbound(d,      1) /= 3) call abort
   if (lbound(d(3:5), 1) /= 1) call abort
-  if (lbound(d%c,    1) /= 1) call abort  
-  if (ubound(d,      1) /= 8) call abort  
+  if (lbound(d%c,    1) /= 1) call abort
+  if (ubound(d,      1) /= 8) call abort
   if (ubound(d(3:5), 1) /= 3) call abort
   if (ubound(d%c,    1) /= 6) call abort  
 
@@ -24,7 +28,48 @@
   if (ucobound(e,   1) /=  9) call abort
   if (ucobound(e%c, 1) /=  9) call abort
   ! no simplification for ucobound(e{,%c}, dim=2)
+
+  if (any(lbound(d     ) /= [3])) call abort
+  if (any(lbound(d(3:5)) /= [1])) call abort
+  if (any(lbound(d%c   ) /= [1])) call abort
+  if (any(ubound(d     ) /= [8])) call abort
+  if (any(ubound(d(3:5)) /= [3])) call abort
+  if (any(ubound(d%c   ) /= [6])) call abort  
+
+  if (any(lcobound(e  ) /=  [5, -1])) call abort
+  if (any(lcobound(e%c) /=  [5, -1])) call abort
+  ! no simplification for ucobound(e{,%c})
+
+  call test_empty_arrays(h, j, k)
+
+contains
+  subroutine test_empty_arrays(a, c, d)
+    type(t) :: a(:), c(-3:0), d(3:1)
+    type(t) :: f(4:2), g(0:6)
+
+    if (lbound(a, 1) /=  1) call abort
+    if (lbound(c, 1) /= -3) call abort
+    if (lbound(d, 1) /=  1) call abort
+    if (lbound(f, 1) /=  1) call abort
+    if (lbound(g, 1) /=  0) call abort
+
+    if (ubound(c, 1) /=  0) call abort
+    if (ubound(d, 1) /=  0) call abort
+    if (ubound(f, 1) /=  0) call abort
+    if (ubound(g, 1) /=  6) call abort
+
+    if (any(lbound(a) /= [ 1])) call abort
+    if (any(lbound(c) /= [-3])) call abort
+    if (any(lbound(d) /= [ 1])) call abort
+    if (any(lbound(f) /= [ 1])) call abort
+    if (any(lbound(g) /= [ 0])) call abort
+
+    if (any(ubound(c) /= [0])) call abort
+    if (any(ubound(d) /= [0])) call abort
+    if (any(ubound(f) /= [0])) call abort
+    if (any(ubound(g) /= [6])) call abort
+
+  end subroutine
 end
-! { dg-final { scan-tree-dump-not "bound" "original" } }
 ! { dg-final { scan-tree-dump-not "abort" "original" } }
 ! { dg-final { cleanup-tree-dump "original" } }



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

* Re: [Patch, Fortran] Simplify lbound
  2015-04-27 18:45   ` Thomas Koenig
  2015-04-27 19:22     ` Thomas Koenig
  2015-04-30 18:46     ` Mikael Morin
@ 2015-05-02 10:50     ` H.J. Lu
  2 siblings, 0 replies; 14+ messages in thread
From: H.J. Lu @ 2015-05-02 10:50 UTC (permalink / raw)
  To: Thomas Koenig; +Cc: Mikael Morin, fortran, gcc-patches

On Mon, Apr 27, 2015 at 11:45 AM, Thomas Koenig <tkoenig@netcologne.de> wrote:
> Am 25.04.2015 um 20:12 schrieb Mikael Morin:
>
>> I've double-checked in the standard, and it seems it is not possible to
>> simplify after all:
>>
>>       If ARRAY is a whole array and either ARRAY is an assumed-size
>>       array of rank DIM or dimension DIM of ARRAY has nonzero extent,
>>       LBOUND (ARRAY, DIM) has a value equal to the lower bound for
>>       subscript DIM of ARRAY. Otherwise the result value is 1.
>>
>> We can't tell whether the array is zero-sized, so we can't tell the
>> lbound value.
>
> So it is only possible to simplify LBOUND if the lower bound is
> equal to one, both for assumed-shape and explicit-shape arrays...
> OK.
>
> The attached patch does that, including a test case which catches
> that particular case.
>
>> As you may want to simplify in the limited scope of the matmul inlining,
>> I'm giving comments about the patch (otherwise you can ignore them):
>>  - No need to check for allocatable or pointer, it should be excluded by
>> as->type == AS_ASSUMED_SHAPE (but does no harm either).
>
> Actually, no.  You can have assumed-shape allocatable or pointer
> dummy arguments which keep their original lbound; see the subroutine
> 'bar' in the test case.
>
>>  - Please modify the early return condition:
>>      if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
>>               || as->type == AS_ASSUMED_RANK))
>>        return NULL;
>>    and let the existing code do the simplification work.
>
> That is not part of my patch.
>
>> Or drop the lbound simplification idea, and fetch the lbound "by hand"
>> at matmul inline time.
>
> I will probably do so as a future optimization, but I think that most
> people will see no reason for using different lower bounds, so it is
> OK for the time being to (slightly) pessimize this case.
>
> So... here is the new patch.  OK for trunk?
>
>         Thomas
>
> 2015-04-25  Thomas Koenig  <tkoenig@gcc.gnu.org>
>
>         PR fortran/37131
>         * simplify.c (simplify_bound): Get constant lower bounds of one
>         from array spec for assumed and explicit shape shape arrays if
>         the lower bounds are indeed one.
>
> 2015-04-25  Thomas Koenig  <tkoenig@gcc.gnu.org>
>
>         PR fortran/37131
>         * gfortran.dg/coarray_lib_this_image_2.f90:  Adjust
>         scan pattern.
>         * gfortran.dg/bound_9.f90:  New test case.
>

This caused:

https://gcc.gnu.org/bugzilla/show_bug.cgi?id=65981


-- 
H.J.

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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-01 21:04       ` Mikael Morin
@ 2015-05-03 20:38         ` Thomas Koenig
  2015-05-10 13:59           ` Mikael Morin
  0 siblings, 1 reply; 14+ messages in thread
From: Thomas Koenig @ 2015-05-03 20:38 UTC (permalink / raw)
  To: Mikael Morin, fortran, gcc-patches

Hi Mikael,

Looks good.

In general, it is better to restrict changes to existing test cases to
the necessary minimum that they still pass, and add new code to new
test cases.  This makes regressions easier to track.

So, OK with that change.

	Thomas

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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-03 20:38         ` Thomas Koenig
@ 2015-05-10 13:59           ` Mikael Morin
  2015-05-10 20:43             ` H.J. Lu
  0 siblings, 1 reply; 14+ messages in thread
From: Mikael Morin @ 2015-05-10 13:59 UTC (permalink / raw)
  To: Thomas Koenig, fortran, gcc-patches

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

Le 03/05/2015 22:38, Thomas Koenig a écrit :
> Hi Mikael,
> 
> Looks good.
> 
> In general, it is better to restrict changes to existing test cases to
> the necessary minimum that they still pass, and add new code to new
> test cases.  This makes regressions easier to track.
> 
> So, OK with that change.
> 
Here is what I have committed.

Mikael

[-- Warning: decoded text below may be mangled, UTF-8 assumed --]
[-- Attachment #2: r222979.diff --]
[-- Type: text/x-patch; name="r222979.diff", Size: 7474 bytes --]

Index: testsuite/gfortran.dg/bound_simplification_5.f90
===================================================================
--- testsuite/gfortran.dg/bound_simplification_5.f90	(révision 0)
+++ testsuite/gfortran.dg/bound_simplification_5.f90	(révision 222979)
@@ -0,0 +1,75 @@
+! { dg-do run }
+! { dg-additional-options "-fcoarray=single -fdump-tree-original" }
+!
+! Check that {L,U}{,CO}BOUND intrinsics are properly simplified.
+!
+  implicit none
+
+  type :: t
+    integer :: c
+  end type t
+
+  type(t) :: d(3:8) = t(7)
+  type(t) :: e[5:9,-1:*]
+  type(t) :: h(3), j(4), k(0)
+
+  !Test full arrays vs subarrays
+  if (lbound(d,      1) /= 3) call abort
+  if (lbound(d(3:5), 1) /= 1) call abort
+  if (lbound(d%c,    1) /= 1) call abort
+  if (ubound(d,      1) /= 8) call abort
+  if (ubound(d(3:5), 1) /= 3) call abort
+  if (ubound(d%c,    1) /= 6) call abort  
+
+  if (lcobound(e,   1) /=  5) call abort
+  if (lcobound(e%c, 1) /=  5) call abort
+  if (lcobound(e,   2) /= -1) call abort
+  if (lcobound(e%c, 2) /= -1) call abort
+  if (ucobound(e,   1) /=  9) call abort
+  if (ucobound(e%c, 1) /=  9) call abort
+  ! no simplification for ucobound(e{,%c}, dim=2)
+
+  if (any(lbound(d     ) /= [3])) call abort
+  if (any(lbound(d(3:5)) /= [1])) call abort
+  if (any(lbound(d%c   ) /= [1])) call abort
+  if (any(ubound(d     ) /= [8])) call abort
+  if (any(ubound(d(3:5)) /= [3])) call abort
+  if (any(ubound(d%c   ) /= [6])) call abort  
+
+  if (any(lcobound(e  ) /=  [5, -1])) call abort
+  if (any(lcobound(e%c) /=  [5, -1])) call abort
+  ! no simplification for ucobound(e{,%c})
+
+  call test_empty_arrays(h, j, k)
+
+contains
+  subroutine test_empty_arrays(a, c, d)
+    type(t) :: a(:), c(-3:0), d(3:1)
+    type(t) :: f(4:2), g(0:6)
+
+    if (lbound(a, 1) /=  1) call abort
+    if (lbound(c, 1) /= -3) call abort
+    if (lbound(d, 1) /=  1) call abort
+    if (lbound(f, 1) /=  1) call abort
+    if (lbound(g, 1) /=  0) call abort
+
+    if (ubound(c, 1) /=  0) call abort
+    if (ubound(d, 1) /=  0) call abort
+    if (ubound(f, 1) /=  0) call abort
+    if (ubound(g, 1) /=  6) call abort
+
+    if (any(lbound(a) /= [ 1])) call abort
+    if (any(lbound(c) /= [-3])) call abort
+    if (any(lbound(d) /= [ 1])) call abort
+    if (any(lbound(f) /= [ 1])) call abort
+    if (any(lbound(g) /= [ 0])) call abort
+
+    if (any(ubound(c) /= [0])) call abort
+    if (any(ubound(d) /= [0])) call abort
+    if (any(ubound(f) /= [0])) call abort
+    if (any(ubound(g) /= [6])) call abort
+
+  end subroutine
+end
+! { dg-final { scan-tree-dump-not "abort" "original" } }
+! { dg-final { cleanup-tree-dump "original" } }
Index: testsuite/ChangeLog
===================================================================
--- testsuite/ChangeLog	(révision 222978)
+++ testsuite/ChangeLog	(révision 222979)
@@ -1,3 +1,7 @@
+2015-05-10  Mikael Morin  <mikael@gcc.gnu.org>
+
+	* gfortran.dg/bound_simplification_5.f90: New.
+
 2015-05-09  Jason Merrill  <jason@redhat.com>
 
 	* lib/target-supports.exp (cxx_default): New global.
Index: fortran/ChangeLog
===================================================================
--- fortran/ChangeLog	(révision 222978)
+++ fortran/ChangeLog	(révision 222979)
@@ -1,3 +1,11 @@
+2015-05-10  Mikael Morin  <mikael@gcc.gnu.org>
+
+	* simplify.c (simplify_bound_dim): Don't check for emptyness
+	in the case of cobound simplification.  Factor lower/upper
+	bound differenciation before the actual simplification.
+	(simplify_bound): Remove assumed shape specific simplification.  
+	Don't give up early for the lbound of an assumed shape.
+
 2015-05-09  Mikael Morin  <mikael@gcc.gnu.org>
 
 	PR fortran/65894
Index: fortran/simplify.c
===================================================================
--- fortran/simplify.c	(révision 222978)
+++ fortran/simplify.c	(révision 222979)
@@ -3340,29 +3340,43 @@
   /* Then, we need to know the extent of the given dimension.  */
   if (coarray || (ref->u.ar.type == AR_FULL && !ref->next))
     {
+      gfc_expr *declared_bound;
+      int empty_bound;
+      bool constant_lbound, constant_ubound;
+
       l = as->lower[d-1];
       u = as->upper[d-1];
 
-      if (l->expr_type != EXPR_CONSTANT || u == NULL
-	  || u->expr_type != EXPR_CONSTANT)
+      gcc_assert (l != NULL);
+
+      constant_lbound = l->expr_type == EXPR_CONSTANT;
+      constant_ubound = u && u->expr_type == EXPR_CONSTANT;
+
+      empty_bound = upper ? 0 : 1;
+      declared_bound = upper ? u : l;
+
+      if ((!upper && !constant_lbound)
+	  || (upper && !constant_ubound))
 	goto returnNull;
 
-      if (mpz_cmp (l->value.integer, u->value.integer) > 0)
+      if (!coarray)
 	{
-	  /* Zero extent.  */
-	  if (upper)
-	    mpz_set_si (result->value.integer, 0);
+	  /* For {L,U}BOUND, the value depends on whether the array
+	     is empty.  We can nevertheless simplify if the declared bound
+	     has the same value as that of an empty array, in which case
+	     the result isn't dependent on the array emptyness.  */
+	  if (mpz_cmp_si (declared_bound->value.integer, empty_bound) == 0)
+	    mpz_set_si (result->value.integer, empty_bound);
+	  else if (!constant_lbound || !constant_ubound)
+	    /* Array emptyness can't be determined, we can't simplify.  */
+	    goto returnNull;
+	  else if (mpz_cmp (l->value.integer, u->value.integer) > 0)
+	    mpz_set_si (result->value.integer, empty_bound);
 	  else
-	    mpz_set_si (result->value.integer, 1);
+	    mpz_set (result->value.integer, declared_bound->value.integer);
 	}
       else
-	{
-	  /* Nonzero extent.  */
-	  if (upper)
-	    mpz_set (result->value.integer, u->value.integer);
-	  else
-	    mpz_set (result->value.integer, l->value.integer);
-	}
+	mpz_set (result->value.integer, declared_bound->value.integer);
     }
   else
     {
@@ -3442,43 +3456,16 @@
 
  done:
 
-  /* If the array shape is assumed shape or explicit, we can simplify lbound
-     to 1 if the given lower bound is one because this matches what lbound
-     should return for an empty array.  */
+  if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_RANK
+	     || (as->type == AS_ASSUMED_SHAPE && upper)))
+    return NULL;
 
-  if (!upper && as && dim && dim->expr_type == EXPR_CONSTANT
-      && (as->type == AS_ASSUMED_SHAPE || as->type == AS_EXPLICIT) 
-      && ref->u.ar.type != AR_SECTION)
-    {
-      /* Watch out for allocatable or pointer dummy arrays, they can have
-	 lower bounds that are not equal to one.  */
-      if (!(array->symtree && array->symtree->n.sym
-	    && (array->symtree->n.sym->attr.allocatable
-		|| array->symtree->n.sym->attr.pointer)))
-	{
-	  unsigned long int ndim;
-	  gfc_expr *lower, *res;
+  gcc_assert (!as
+	      || (as->type != AS_DEFERRED
+		  && array->expr_type == EXPR_VARIABLE
+		  && !array->symtree->n.sym->attr.allocatable
+		  && !array->symtree->n.sym->attr.pointer));
 
-	  ndim = mpz_get_si (dim->value.integer) - 1;
-	  lower = as->lower[ndim];
-	  if (lower->expr_type == EXPR_CONSTANT
-	      && mpz_cmp_si (lower->value.integer, 1) == 0)
-	    {
-	      res = gfc_copy_expr (lower);
-	      if (kind)
-		{
-		  int nkind = mpz_get_si (kind->value.integer);
-		  res->ts.kind = nkind;
-		}
-	      return res;
-	    }
-	}
-    }
-
-  if (as && (as->type == AS_DEFERRED || as->type == AS_ASSUMED_SHAPE
-	     || as->type == AS_ASSUMED_RANK))
-    return NULL;
-
   if (dim == NULL)
     {
       /* Multi-dimensional bounds.  */


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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-10 13:59           ` Mikael Morin
@ 2015-05-10 20:43             ` H.J. Lu
  2015-05-10 22:08               ` Thomas Koenig
  0 siblings, 1 reply; 14+ messages in thread
From: H.J. Lu @ 2015-05-10 20:43 UTC (permalink / raw)
  To: Mikael Morin; +Cc: Thomas Koenig, fortran, gcc-patches

On Sun, May 10, 2015 at 6:58 AM, Mikael Morin <mikael.morin@sfr.fr> wrote:
> Le 03/05/2015 22:38, Thomas Koenig a écrit :
>> Hi Mikael,
>>
>> Looks good.
>>
>> In general, it is better to restrict changes to existing test cases to
>> the necessary minimum that they still pass, and add new code to new
>> test cases.  This makes regressions easier to track.
>>
>> So, OK with that change.
>>
> Here is what I have committed.
>

It caused:

/export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:39:
Error: Variable 'c1' cannot appear in the expression at (1)^M
/export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:42:
Error: Variable 'c2' cannot appear in the expression at (1)^M
/export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:15:
Error: Variable 'a1' cannot appear in the expression at (1)^M
/export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:18:
Error: Variable 'a2' cannot appear in the expression at (1)^M
/export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:27:
Error: Variable 'b1' cannot appear in the expression at (1)^M
/export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:30:
Error: Variable 'b2' cannot appear in the expression at (1)^M

FAIL: gfortran.dg/inline_matmul_3.f90   -O  (test for excess errors)

-- 
H.J.

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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-10 20:43             ` H.J. Lu
@ 2015-05-10 22:08               ` Thomas Koenig
  2015-05-11 13:17                 ` Mikael Morin
  0 siblings, 1 reply; 14+ messages in thread
From: Thomas Koenig @ 2015-05-10 22:08 UTC (permalink / raw)
  To: fortran; +Cc: gcc-patches, Mikael Morin

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

Am 10.05.2015 um 22:43 schrieb H.J. Lu:

>> Here is what I have committed.
>>
> 
> It caused:
> 
> /export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:39:
> Error: Variable 'c1' cannot appear in the expression at (1)^M

I know that error message, I got it when developing the inline
matmul patches with the same test cases.  I had a fix for this
error message in one of my matmul patches, but it was removed
in the review process because it could no longer be reproduced.

So, here is the fix again.  I think it is close to obvious (since it
fixes the problem and can obviously do no harm), but anyway:  OK for
trunk?

Regards

	Thomas

2015-05-10  Thomas Koenig  <tkoenig@gcc.gnu.org>

	PR fortran/66041
	PR fortran/37131
	* gfortran.h (gfc_array_spec):  Add field resolved.
	* array.c (gfc_resolve_array_spec):  Resolve array spec
	only once.


[-- Attachment #2: p-fix.diff --]
[-- Type: text/x-patch, Size: 866 bytes --]

Index: array.c
===================================================================
--- array.c	(Revision 222984)
+++ array.c	(Arbeitskopie)
@@ -338,6 +338,9 @@ gfc_resolve_array_spec (gfc_array_spec *as, int ch
   if (as == NULL)
     return true;
 
+  if (as->resolved)
+    return true;
+
   for (i = 0; i < as->rank + as->corank; i++)
     {
       e = as->lower[i];
@@ -364,6 +367,8 @@ gfc_resolve_array_spec (gfc_array_spec *as, int ch
 	}
     }
 
+  as->resolved = true;
+
   return true;
 }
 
Index: gfortran.h
===================================================================
--- gfortran.h	(Revision 222984)
+++ gfortran.h	(Arbeitskopie)
@@ -1002,6 +1002,8 @@ typedef struct
   bool cp_was_assumed; /* AS_ASSUMED_SIZE cp arrays are converted to
 			AS_EXPLICIT, but we want to remember that we
 			did this.  */
+
+  bool resolved;
 }
 gfc_array_spec;
 

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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-10 22:08               ` Thomas Koenig
@ 2015-05-11 13:17                 ` Mikael Morin
  2015-05-12  7:08                   ` Thomas Koenig
  0 siblings, 1 reply; 14+ messages in thread
From: Mikael Morin @ 2015-05-11 13:17 UTC (permalink / raw)
  To: Thomas Koenig, fortran; +Cc: gcc-patches

Le 11/05/2015 00:08, Thomas Koenig a écrit :
> Am 10.05.2015 um 22:43 schrieb H.J. Lu:
> 
>>> Here is what I have committed.
>>>
>>
>> It caused:
>>
>> /export/gnu/import/git/sources/gcc/gcc/testsuite/gfortran.dg/inline_matmul_3.f90:38:39:
>> Error: Variable 'c1' cannot appear in the expression at (1)^M
> 
> I know that error message, I got it when developing the inline
> matmul patches with the same test cases.  I had a fix for this
> error message in one of my matmul patches, but it was removed
> in the review process because it could no longer be reproduced.
> 
> So, here is the fix again.  I think it is close to obvious (since it
> fixes the problem and can obviously do no harm), but anyway:  OK for
> trunk?
> 
For what it's worth, I have looked at it further, and it seems to be
gfc_current_ns not being set to the internal namespace.
A patch like this also removes the error.

Index: frontend-passes.c
===================================================================
--- frontend-passes.c	(révision 223002)
+++ frontend-passes.c	(copie de travail)
@@ -581,6 +581,9 @@ insert_block ()
   else
     ns = inserted_block->ext.block.ns;

+  /* From now on, everything will happen in the inserted block.  */
+  gfc_current_ns = ns;
+
   return ns;
 }

To be honest, both patches look fragile to me. Yours because it leaves
gfc_current_ns to its value, leaving the door open to other problems.
Mine, well, because it's playing with a global variable, with the
possible side-effects this could have.
However, without a better idea, I'm OK with either patch (or both).

Mikael

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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-11 13:17                 ` Mikael Morin
@ 2015-05-12  7:08                   ` Thomas Koenig
  2015-05-12 10:04                     ` Mikael Morin
  0 siblings, 1 reply; 14+ messages in thread
From: Thomas Koenig @ 2015-05-12  7:08 UTC (permalink / raw)
  To: Mikael Morin, fortran; +Cc: gcc-patches

Hi Mikael,


> To be honest, both patches look fragile to me. Yours because it leaves
> gfc_current_ns to its value, leaving the door open to other problems.
> Mine, well, because it's playing with a global variable, with the
> possible side-effects this could have.
> However, without a better idea, I'm OK with either patch (or both).

I have found that playing around with gfc_current_ns can be quite
dangerous and can cause regressions in unexpected places.  Specifically,
I tried wrapping the callers to create_var and insert_block in
save/restore wrappers for gfc_current_ns, and that caused quite
a few very strange regressions.

So, working on the theory that a fix that may leave unknown problems
open is better than a fix that may introduce unknown problems, and
in order to get the regression out of the way, I have committed the
patch preventing multiple resolution of an array spec.

Maybe we should open a PR for auditing the use of gfc_current_ns
in front-end optmiization.

Regards

	Thomas


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

* Re: [Patch, Fortran] Simplify lbound
  2015-05-12  7:08                   ` Thomas Koenig
@ 2015-05-12 10:04                     ` Mikael Morin
  0 siblings, 0 replies; 14+ messages in thread
From: Mikael Morin @ 2015-05-12 10:04 UTC (permalink / raw)
  To: Thomas Koenig, fortran; +Cc: gcc-patches

Le 12/05/2015 08:43, Thomas Koenig a écrit :
> Hi Mikael,
> 
> 
>> To be honest, both patches look fragile to me. Yours because it leaves
>> gfc_current_ns to its value, leaving the door open to other problems.
>> Mine, well, because it's playing with a global variable, with the
>> possible side-effects this could have.
>> However, without a better idea, I'm OK with either patch (or both).
> 
> I have found that playing around with gfc_current_ns can be quite
> dangerous and can cause regressions in unexpected places.  Specifically,
> I tried wrapping the callers to create_var and insert_block in
> save/restore wrappers for gfc_current_ns, and that caused quite
> a few very strange regressions.
> 
> So, working on the theory that a fix that may leave unknown problems
> open is better than a fix that may introduce unknown problems, and
> in order to get the regression out of the way, I have committed the
> patch preventing multiple resolution of an array spec.
> 
thanks.

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

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

Thread overview: 14+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
2015-04-25 11:34 [Patch, Fortran] Simplify lbound Thomas Koenig
2015-04-25 18:13 ` Mikael Morin
2015-04-27 18:45   ` Thomas Koenig
2015-04-27 19:22     ` Thomas Koenig
2015-04-30 18:46     ` Mikael Morin
2015-05-01 21:04       ` Mikael Morin
2015-05-03 20:38         ` Thomas Koenig
2015-05-10 13:59           ` Mikael Morin
2015-05-10 20:43             ` H.J. Lu
2015-05-10 22:08               ` Thomas Koenig
2015-05-11 13:17                 ` Mikael Morin
2015-05-12  7:08                   ` Thomas Koenig
2015-05-12 10:04                     ` Mikael Morin
2015-05-02 10:50     ` H.J. Lu

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