re PR fortran/19181 (ICE and segmentation fault with pointer member in user defined type)
2005-09-18 Paul Thomas <pault@gcc.gnu.org> PR fortran/19181 * gfortran.dg/derived_pointer_null_1.f90: New test. From-SVN: r104403
This commit is contained in:
parent
c295372571
commit
30bf3b40e6
2 changed files with 37 additions and 0 deletions
|
@ -1,3 +1,8 @@
|
|||
2005-09-18 Paul Thomas <pault@gcc.gnu.org>
|
||||
|
||||
PR fortran/19181
|
||||
* gfortran.dg/derived_pointer_null_1.f90: New test.
|
||||
|
||||
2005-09-18 Richard Guenther <rguenther@suse.de>
|
||||
|
||||
PR middle-end/23944
|
||||
|
|
32
gcc/testsuite/gfortran.dg/derived_pointer_null_1.f90
Normal file
32
gcc/testsuite/gfortran.dg/derived_pointer_null_1.f90
Normal file
|
@ -0,0 +1,32 @@
|
|||
! { dg-do compile }
|
||||
! { dg-options "-std=gnu" }
|
||||
!
|
||||
! Test of fix (patch unknown) for pr19181 and pr21300. This test is based
|
||||
! on the example given in 21300. Note that this can be executed.
|
||||
!
|
||||
! Contributed by Paul Thomas <pault@gnu.org>
|
||||
!
|
||||
TYPE ast_obs
|
||||
real, DIMENSION(:), POINTER :: geopos
|
||||
END TYPE ast_obs
|
||||
|
||||
TYPE(ast_obs), PARAMETER :: undefined_ast_obs = AST_OBS(NULL())
|
||||
type(ast_obs) :: my_ast_obs
|
||||
real, target, dimension(10) :: rt
|
||||
|
||||
my_ast_obs%geopos => rt
|
||||
if (.not.associated (my_ast_obs%geopos)) call abort ()
|
||||
|
||||
call get_null_ast_obs (my_ast_obs)
|
||||
if (associated (my_ast_obs%geopos)) call abort ()
|
||||
|
||||
CONTAINS
|
||||
|
||||
SUBROUTINE get_null_ast_obs (obs1)
|
||||
TYPE(ast_obs) :: obs1
|
||||
obs1 = undefined_ast_obs
|
||||
RETURN
|
||||
END SUBROUTINE get_null_ast_obs
|
||||
|
||||
END
|
||||
|
Loading…
Add table
Reference in a new issue