backport: re PR fortran/80121 (Memory leak with derived-type intent(out) argument)

2017-05-05  Janus Weil  <janus@gcc.gnu.org>

	Backport from trunk
	PR fortran/80121
	* trans-expr.c (gfc_conv_procedure_call): Deallocate the components
	of allocatable intent(out) arguments.


2017-05-05  Janus Weil  <janus@gcc.gnu.org>

	Backport from trunk
	PR fortran/80121
	* gfortran.dg/intent_out_9.f90: New test case.

From-SVN: r247662
This commit is contained in:
Janus Weil 2017-05-05 23:00:53 +02:00
parent 52637de8cc
commit 533a17774d
4 changed files with 50 additions and 0 deletions

View File

@ -1,3 +1,10 @@
2017-05-05 Janus Weil <janus@gcc.gnu.org>
Backport from trunk
PR fortran/80121
* trans-expr.c (gfc_conv_procedure_call): Deallocate the components
of allocatable intent(out) arguments.
2017-05-05 Janus Weil <janus@gcc.gnu.org>
Backport from trunk

View File

@ -5454,6 +5454,16 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
if (fsym && fsym->attr.allocatable
&& fsym->attr.intent == INTENT_OUT)
{
if (fsym->ts.type == BT_DERIVED
&& fsym->ts.u.derived->attr.alloc_comp)
{
// deallocate the components first
tmp = gfc_deallocate_alloc_comp (fsym->ts.u.derived,
parmse.expr, e->rank);
if (tmp != NULL_TREE)
gfc_add_expr_to_block (&se->pre, tmp);
}
tmp = build_fold_indirect_ref_loc (input_location,
parmse.expr);
if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (tmp)))

View File

@ -1,3 +1,9 @@
2017-05-05 Janus Weil <janus@gcc.gnu.org>
Backport from trunk
PR fortran/80121
* gfortran.dg/intent_out_9.f90: New test case.
2017-05-05 Janus Weil <janus@gcc.gnu.org>
Backport from trunk

View File

@ -0,0 +1,27 @@
! { dg-do compile }
! { dg-options "-fdump-tree-original" }
!
! PR 80121: Memory leak with derived-type intent(out) argument
!
! Contributed by Andrew Wood <andrew@fluidgravity.co.uk>
PROGRAM p
IMPLICIT NONE
TYPE t1
INTEGER, ALLOCATABLE :: i(:)
END TYPE
call leak
CONTAINS
SUBROUTINE s1(e)
TYPE(t1), ALLOCATABLE, INTENT(OUT) :: e(:)
ALLOCATE( e(1) )
ALLOCATE( e(1)%i(2) )
END SUBROUTINE
SUBROUTINE leak
TYPE(t1), ALLOCATABLE :: e(:)
CALL s1(e)
CALL s1(e)
END SUBROUTINE
END PROGRAM
! { dg-final { scan-tree-dump-times "__builtin_free" 6 "original" } }