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  <tkoe...@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  <tkoe...@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.
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" } }
! { 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" } }

Reply via email to