[multiple changes]

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
This commit is contained in:
Tobias Burnus 2010-02-24 08:00:35 +01:00 committed by Tobias Burnus
parent d8a06a8231
commit 505a36f95b
4 changed files with 68 additions and 0 deletions

View 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

View 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)

View 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

View File

@ -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" } }