Commit 3cae214f by Paul Thomas

[multiple changes]

2016-11-25  Andre Vehreschild  <vehre@gcc.gnu.org>
	Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/78293
	* trans-expr.c (gfc_conv_procedure_call): Prepend deallocation
	of alloctable components to post, rather than adding to
	se->post.
	* trans-stmt.c (gfc_trans_allocate): Move deallocation of expr3
	allocatable components so that all expr3s are visited.

2016-11-25  Paul Thomas  <pault@gcc.gnu.org>

	PR fortran/78293
	* gfortran.dg/allocatable_function_10.f90: New test.
	* gfortran.dg/class_array_15.f03: Increase builtin_free count
	from 11 to 12.

From-SVN: r242875
parent ae22bc5d
2016-11-25 Andre Vehreschild <vehre@gcc.gnu.org>
Paul Thomas <pault@gcc.gnu.org>
PR fortran/78293
* trans-expr.c (gfc_conv_procedure_call): Prepend deallocation
of alloctable components to post, rather than adding to
se->post.
* trans-stmt.c (gfc_trans_allocate): Move deallocation of expr3
allocatable components so that all expr3s are visited.
2016-11-25 Paul Thomas <pault@gcc.gnu.org>
PR fortran/78293
* gfortran.dg/allocatable_function_10.f90: New test.
* gfortran.dg/class_array_15.f03: Increase builtin_free count
from 11 to 12.
2016-11-24 Steven G. Kargl <kargl@gcc.gnu.org>
PR fortran/78500
......
......@@ -5568,7 +5568,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
tmp = gfc_deallocate_alloc_comp (e->ts.u.derived, tmp, parm_rank);
gfc_add_expr_to_block (&se->post, tmp);
gfc_prepend_expr_to_block (&post, tmp);
}
/* Add argument checking of passing an unallocated/NULL actual to
......
......@@ -5684,17 +5684,6 @@ gfc_trans_allocate (gfc_code * code)
}
gfc_add_modify_loc (input_location, &block, var, tmp);
/* Deallocate any allocatable components after all the allocations
and assignments of expr3 have been completed. */
if (code->expr3->ts.type == BT_DERIVED
&& code->expr3->rank == 0
&& code->expr3->ts.u.derived->attr.alloc_comp)
{
tmp = gfc_deallocate_alloc_comp (code->expr3->ts.u.derived,
var, 0);
gfc_add_expr_to_block (&post, tmp);
}
expr3 = var;
if (se.string_length)
/* Evaluate it assuming that it also is complicated like expr3. */
......@@ -5705,6 +5694,20 @@ gfc_trans_allocate (gfc_code * code)
expr3 = se.expr;
expr3_len = se.string_length;
}
/* Deallocate any allocatable components in expressions that use a
temporary, i.e. are not of expr-type EXPR_VARIABLE or force the
use of a temporary, after the assignment of expr3 is completed. */
if ((code->expr3->ts.type == BT_DERIVED
|| code->expr3->ts.type == BT_CLASS)
&& (code->expr3->expr_type != EXPR_VARIABLE || temp_var_needed)
&& code->expr3->ts.u.derived->attr.alloc_comp)
{
tmp = gfc_deallocate_alloc_comp (code->expr3->ts.u.derived,
expr3, code->expr3->rank);
gfc_prepend_expr_to_block (&post, tmp);
}
/* Store what the expr3 is to be used for. */
if (e3_is == E3_UNSET)
e3_is = expr3 != NULL_TREE ?
......
2016-11-25 Paul Thomas <pault@gcc.gnu.org>
PR fortran/78293
* gfortran.dg/allocatable_function_10.f90: New test.
* gfortran.dg/class_array_15.f03: Increase builtin_free count
from 11 to 12.
2016-11-25 Bin Cheng <bin.cheng@arm.com>
PR middle-end/78507
......@@ -45,7 +52,7 @@
2016-11-25 Senthil Kumar Selvaraj <senthil_kumar.selvaraj@atmel.com>
* gcc.dg/pr64277.c: Use __INT32_TYPE__ for targets
with sizeof(int) < 4.
with sizeof(int) < 4.
2016-11-24 Martin Sebor <msebor@redhat.com>
......
! { dg-do run }
!
! Test the fix for PR78293. The deallocations are present at the
! end of the main programme to aid memory leak searching. The
! allocation in 'tt' leaked memory from an intermediate temporary
! for the array constructor.
!
! Contributed by Andrew Benson <abensonca@gmail.com>
!
module m
implicit none
type t
integer, allocatable, dimension(:) :: r
end type t
contains
function tt(a,b)
implicit none
type(t), allocatable, dimension(:) :: tt
type(t), intent(in), dimension(:) :: a,b
allocate(tt, source = [a,b])
end function tt
function ts(arg)
implicit none
type(t), allocatable, dimension(:) :: ts
integer, intent(in) :: arg(:)
allocate(ts(1))
allocate(ts(1)%r, source = arg)
return
end function ts
end module m
program p
use m
implicit none
type(t), dimension(2) :: c
c=tt(ts([99,199,1999]),ts([42,142]))
if (any (c(1)%r .ne. [99,199,1999])) call abort
if (any (c(2)%r .ne. [42,142])) call abort
deallocate(c(1)%r)
deallocate(c(2)%r)
end program p
......@@ -115,4 +115,4 @@ subroutine pr54992 ! This test remains as the original.
bh => bhGet(b,instance=2)
if (loc (b) .ne. loc(bh%hostNode)) call abort
end
! { dg-final { scan-tree-dump-times "builtin_free" 11 "original" } }
! { dg-final { scan-tree-dump-times "builtin_free" 12 "original" } }
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