This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

[Patch,Fortran] PR 43042 - fix -fwhole-file ICE for C_NULL_PTR DT init


Hello,

the patch fixes an ICE found when compiling the gfortran testsuite with
LTO (-flto), but -fwhole-file is enough to trigger the ICE.

On one hand, C_NULL_PTR is a derived types (DT) with hidden components -
but on the other hand it is just NULL (the integer number 0). The ICE
comes about in gfc_conv_initializer. First the DT is replaced by the
integer expression (EXPR_CONST), but if "ts" (= function argument, not
expr->ts) has ts->type == BT_DERIVED, one enters gfc_conv_structure -
and ICEs there.

The solution is simple: Call directly in the if branch gfc_conv_constant
and exit.

Build and regtested on x86-64-linux. OK for the trunk?

Tobias
2010-02-23  Tobias Burnus  <burnus@net-b.de>

	PR fortran/43042
	* trans-expr.c (gfc_conv_initializer): Call directly
	gfc_conv_constant for C_NULL_(FUN)PTR.

2010-02-23  Tobias Burnus  <burnus@net-b.de>

	PR fortran/43042
	* gfortran.dg/c_ptr_tests_15.f90: New test.

Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c	(revision 156991)
+++ gcc/fortran/trans-expr.c	(working copy)
@@ -3949,6 +3949,10 @@ gfc_conv_initializer (gfc_expr * expr, g
 	 its kind.  */
       expr->ts.f90_type = derived->ts.f90_type;
       expr->ts.kind = derived->ts.kind;
+
+      gfc_init_se (&se, NULL);
+      gfc_conv_constant (&se, expr);
+      return se.expr;
     }
   
   if (array)
Index: gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90
===================================================================
--- gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90	(revision 0)
+++ gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90	(revision 0)
@@ -0,0 +1,53 @@
+! { dg-do compile }
+! { dg-options "-fwhole-file -fdump-tree-original" }
+!
+! PR fortran/43042 - fix ICE with c_null_ptr when using
+! -fwhole-file (or -flto, which implies -fwhole-file).
+!
+! Testcase based on c_ptr_tests_14.f90  (PR fortran/41298)
+! Check that c_null_ptr default initializer is really applied
+
+module m
+  use iso_c_binding
+  type, public :: fgsl_file
+     type(c_ptr)    :: gsl_file = c_null_ptr
+     type(c_funptr) :: gsl_func = c_null_funptr
+     type(c_ptr)    :: NIptr
+     type(c_funptr) :: NIfunptr
+  end type fgsl_file
+contains
+  subroutine sub(aaa,bbb)
+    type(fgsl_file), intent(out)   :: aaa
+    type(fgsl_file), intent(inout) :: bbb
+  end subroutine
+  subroutine proc() bind(C)
+  end subroutine proc
+end module m
+
+program test
+  use m
+  implicit none
+  type(fgsl_file) :: file, noreinit
+  integer, target :: tgt
+
+  call sub(file, noreinit)
+  if(c_associated(file%gsl_file)) call abort()
+  if(c_associated(file%gsl_func)) call abort()
+
+  file%gsl_file = c_loc(tgt)
+  file%gsl_func = c_funloc(proc)
+  call sub(file, noreinit)
+  if(c_associated(file%gsl_file)) call abort()
+  if(c_associated(file%gsl_func)) call abort()
+end program test
+
+! { dg-final { scan-tree-dump-times "gsl_file = 0B" 1 "original" } }
+! { dg-final { scan-tree-dump-times "gsl_func = 0B" 1 "original" } }
+
+! { dg-final { scan-tree-dump-times "NIptr = 0B"    0 "original" } }
+! { dg-final { scan-tree-dump-times "NIfunptr = 0B" 0 "original" } }
+
+! { dg-final { scan-tree-dump-times "bbb =" 0 "original" } }
+
+! { dg-final { cleanup-tree-dump "original" } }
+! { dg-final { cleanup-modules "m" } }

Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]