Hi all,

the patch in the attachment fixes a memory leak by auto-deallocating
the allocatable components of an allocatable intent(out) argument.

Regtests cleanly on x86_64-linux-gnu. Ok for trunk?

Cheers,
Janus


2017-04-22  Janus Weil  <ja...@gcc.gnu.org>

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

2017-04-22  Janus Weil  <ja...@gcc.gnu.org>

    PR fortran/80121
    * gfortran.dg/intent_out_9.f90: New test case.
Index: gcc/fortran/trans-expr.c
===================================================================
--- gcc/fortran/trans-expr.c    (revision 247077)
+++ gcc/fortran/trans-expr.c    (working copy)
@@ -5454,6 +5454,16 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol *
              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)))
! { dg-do compile }
! { dg-options "-fdump-tree-original" }
!
! PR 80121: Memory leak with derived-type intent(out) argument
!
! Contributed by Andrew Wood <and...@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" } }
! { dg-final { cleanup-tree-dump "original" } }

Reply via email to