Hello,

This fixes a regression introduced by my bound simplification refactoring at
https://gcc.gnu.org/ml/gcc-patches/2015-05/msg00843.html
The assert was introduced in the change above and checks that the
refactoring didn't lose anything regarding the condition used in the
existing code.
The condition was assuming full object arrays, and fails with subobject
arrays.
The fix (attached) is obvious enough.
The testcase is Thomas' reduced one, which is independent on matmul
simplification.

I plan to commit this patch tonight.

Mikael





2015-05-11  Mikael Morin  <mik...@gcc.gnu.org>

        * simplify.c (simplify_bound): Fix assert to accept subobject
        arrays.
Index: simplify.c
===================================================================
--- simplify.c	(révision 222979)
+++ simplify.c	(copie de travail)
@@ -3463,8 +3463,8 @@ simplify_bound (gfc_expr *array, gfc_expr *dim, gf
   gcc_assert (!as
 	      || (as->type != AS_DEFERRED
 		  && array->expr_type == EXPR_VARIABLE
-		  && !array->symtree->n.sym->attr.allocatable
-		  && !array->symtree->n.sym->attr.pointer));
+		  && !gfc_expr_attr (array).allocatable
+		  && !gfc_expr_attr (array).pointer));
 
   if (dim == NULL)
     {


! { dg-do compile }
! { dg-additional-options "-fdump-tree-original" }
!
! PR fortran/66100
! ICE on lbound simplification
!
! Original test case by Joost VandeVondele <joost.vandevond...@mat.ethz.ch>
! Reduced by Thomas Koenig <tkoe...@gcc.gnu.org>
!
MODULE qs_integrate_potential_low
  INTEGER, PARAMETER :: dp = 8
  TYPE cell_type
    REAL(KIND=8) :: h_inv(3,3)
  END TYPE
  TYPE(cell_type), POINTER                 :: cell
  REAL(KIND=dp), DIMENSION(3)              :: rp
  CONTAINS
    SUBROUTINE integrate_general_opt()
    REAL(KIND=dp) :: gp(3)
    INTEGER :: ng
    if (any(lbound(cell%h_inv) /= 1)) call abort
    if (any(ubound(cell%h_inv) /= 3)) call abort
    END SUBROUTINE integrate_general_opt
END MODULE qs_integrate_potential_low
! { dg-final { scan-tree-dump-not "bound" "original" } }
! { dg-final { scan-tree-dump-not "abort" "original" } }
! { dg-final { cleanup-tree-dump "original" } }


Reply via email to