]> git.ipfire.org Git - thirdparty/gcc.git/commitdiff
[multiple changes]
authorTobias Burnus <burnus@net-b.de>
Wed, 24 Feb 2010 07:00:35 +0000 (08:00 +0100)
committerTobias Burnus <burnus@gcc.gnu.org>
Wed, 24 Feb 2010 07:00:35 +0000 (08:00 +0100)
2010-02-24  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-24  Tobias Burnus  <burnus@net-b.de>

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

From-SVN: r157029

gcc/fortran/ChangeLog
gcc/fortran/trans-expr.c
gcc/testsuite/ChangeLog
gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90 [new file with mode: 0644]

index dc650fed5f43ca464beda545aa7b0f944ab5b46c..af4bf20d3f480b397db1f4e5cb3ce26194104cd8 100644 (file)
@@ -1,3 +1,9 @@
+2010-02-24  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-22  Paul Thomas  <pault@gcc.gnu.org>
 
        PR fortran/43072
index d71214884e2a1a42b178f1de95f3042006cacda7..ecb577a2e449e1f467d06dfc0c16cb622b1d429b 100644 (file)
@@ -3949,6 +3949,10 @@ gfc_conv_initializer (gfc_expr * expr, gfc_typespec * ts, tree type,
         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 dc688dd61ee93050a618580d9003daeb51d51cb6..4acf55730cc18bf9e62bc26d49148c6398b67836 100644 (file)
@@ -1,3 +1,8 @@
+2010-02-24  Tobias Burnus  <burnus@net-b.de>
+
+       PR fortran/43042
+       * gfortran.dg/c_ptr_tests_15.f90: New test.
+
 2010-02-23  Jakub Jelinek  <jakub@redhat.com>
 
        PR target/43107
diff --git a/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90 b/gcc/testsuite/gfortran.dg/c_ptr_tests_15.f90
new file mode 100644 (file)
index 0000000..1ce0c15
--- /dev/null
@@ -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" } }