Commit 29eb509c by Andre Vehreschild

re PR fortran/71807 (Internal compiler error with NULL() reference in structure constructor)

gcc/fortran/ChangeLog:

2016-07-15  Andre Vehreschild  <vehre@gcc.gnu.org>

	PR fortran/71807
	* trans-expr.c (gfc_trans_subcomponent_assign): Special casing
	when allocatable component is set to null() in initializer.

gcc/testsuite/ChangeLog:

2016-07-15  Andre Vehreschild  <vehre@gcc.gnu.org>

	PR fortran/71807
	* gfortran.dg/null_9.f90: New test.

From-SVN: r238368
parent 43aabfcf
2016-07-15 Andre Vehreschild <vehre@gcc.gnu.org>
PR fortran/71807
* trans-expr.c (gfc_trans_subcomponent_assign): Special casing
when allocatable component is set to null() in initializer.
2016-07-14 Steven G. Kargl <kargl@gcc.gnu.org>
PR fortran/29819
......
......@@ -7200,6 +7200,12 @@ gfc_trans_subcomponent_assign (tree dest, gfc_component * cm, gfc_expr * expr,
tmp = gfc_trans_alloc_subarray_assign (tmp, cm, expr);
gfc_add_expr_to_block (&block, tmp);
}
else if (init && cm->attr.allocatable && expr->expr_type == EXPR_NULL)
{
/* NULL initialization for allocatable components. */
gfc_add_modify (&block, dest, fold_convert (TREE_TYPE (dest),
null_pointer_node));
}
else if (init && (cm->attr.allocatable
|| (cm->ts.type == BT_CLASS && CLASS_DATA (cm)->attr.allocatable
&& expr->ts.type != BT_CLASS)))
......
2016-07-15 Andre Vehreschild <vehre@gcc.gnu.org>
PR fortran/71807
* gfortran.dg/null_9.f90: New test.
2016-07-15 Bin Cheng <bin.cheng@arm.com>
* gcc.dg/tree-ssa/loop-41.c: New test.
......
! { dg-do run }
MODULE fold_convert_loc_ice
IMPLICIT NONE
PRIVATE
TYPE, PUBLIC :: ta
PRIVATE
INTEGER :: a_comp
END TYPE ta
TYPE, PUBLIC :: tb
TYPE(ta), ALLOCATABLE :: b_comp
END TYPE tb
PUBLIC :: proc
CONTAINS
SUBROUTINE proc
TYPE(tb) :: b
b = tb(null())
if (allocated( b%b_comp )) call abort()
END SUBROUTINE proc
END MODULE fold_convert_loc_ice
USE fold_convert_loc_ice
call proc()
END
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment