The following fixes PR63152 zeroing the data field only for allocatables, not 
pointers. The benefit of the patch is a small speedup, and it avoids that code 
starts to rely on behavior that is undefined in the standard. With this patch, 
something like

INTEGER, DIMENSION(:), POINTER :: foo
IF (ASSOCIATED(foo)) ...

will be detected by valgrind as undefined behavior.

tested on x86_64-unknown-linux-gnu.

OK for trunk ?

Joost
Index: gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90
===================================================================
--- gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90	(revision 215321)
+++ gcc/testsuite/gfortran.dg/auto_char_dummy_array_1.f90	(working copy)
@@ -11,6 +11,8 @@ end module global
 program oh_no_not_pr15908_again
   character(12), dimension(:), pointer :: ptr
 
+  nullify(ptr)
+
   call a (ptr, 12)
   if (.not.associated (ptr) ) call abort ()
   if (any (ptr.ne."abc")) call abort ()
Index: gcc/testsuite/gfortran.dg/pr63152.f90
===================================================================
--- gcc/testsuite/gfortran.dg/pr63152.f90	(revision 0)
+++ gcc/testsuite/gfortran.dg/pr63152.f90	(revision 0)
@@ -0,0 +1,17 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original" }
+!
+! PR 63152 : needless init of local pointer arrays
+!
+! Contributed by Joost VandeVondele <vond...@gcc.gnu.org>
+ SUBROUTINE S1()
+   INTEGER, POINTER, DIMENSION(:) :: v
+   INTERFACE
+    SUBROUTINE foo(v)
+       INTEGER, POINTER, DIMENSION(:) :: v
+    END SUBROUTINE
+   END INTERFACE
+   CALL foo(v)
+ END SUBROUTINE S1
+! { dg-final { scan-tree-dump-times "= 0B" 0 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }
Index: gcc/fortran/trans-array.c
===================================================================
--- gcc/fortran/trans-array.c	(revision 215321)
+++ gcc/fortran/trans-array.c	(working copy)
@@ -8647,8 +8647,8 @@ gfc_trans_deferred_array (gfc_symbol * s
       type = TREE_TYPE (descriptor);
     }
 
-  /* NULLIFY the data pointer.  */
-  if (GFC_DESCRIPTOR_TYPE_P (type) && !sym->attr.save)
+  /* NULLIFY the data pointer, for non-saved allocatables. */
+  if (GFC_DESCRIPTOR_TYPE_P (type) && !sym->attr.save && sym->attr.allocatable)
     gfc_conv_descriptor_data_set (&init, descriptor, null_pointer_node);
 
   gfc_restore_backend_locus (&loc);
gcc/fortran/ChangeLog:

2014-09-17  Joost VandeVondele  <vond...@gcc.gnu.org>

        PR fortran/63152
        * trans-array.c (gfc_trans_deferred_array): Only nullify allocatables.


gcc/testsuite/ChangeLog:

2014-09-17  Joost VandeVondele  <vond...@gcc.gnu.org>

        PR fortran/63152
        * gfortran.dg/auto_char_dummy_array_1.f90: Fix undefined behavior.
        * gfortran.dg/pr63152.f90: New test.

Reply via email to