URL
https://opencores.org/ocsvn/openrisc_me/openrisc_me/trunk
Subversion Repositories openrisc_me
[/] [openrisc/] [trunk/] [gnu-src/] [gcc-4.5.1/] [gcc/] [testsuite/] [gfortran.dg/] [c_ptr_tests_14.f90] - Rev 302
Compare with Previous | Blame | View Log
! { dg-do run }! { dg-options "-fdump-tree-original" }!! PR fortran/41298!! Check that c_null_ptr default initializer is really appliedmodule muse iso_c_bindingtype, public :: fgsl_filetype(c_ptr) :: gsl_file = c_null_ptrtype(c_funptr) :: gsl_func = c_null_funptrtype(c_ptr) :: NIptrtype(c_funptr) :: NIfunptrend type fgsl_filecontainssubroutine sub(aaa,bbb)type(fgsl_file), intent(out) :: aaatype(fgsl_file), intent(inout) :: bbbend subroutinesubroutine proc() bind(C)end subroutine procend module mprogram testuse mimplicit nonetype(fgsl_file) :: file, noreinitinteger, target :: tgtcall 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" } }
