Implement finalization of allocatable for DEALLOCATE, end of scope and intent(out) NOTE: end of scope handling does not yet work, see test case below (too much + too little finalization) diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c index be3a5a0..c84e101 100644 --- a/gcc/fortran/trans-array.c +++ b/gcc/fortran/trans-array.c @@ -7243,7 +7243,7 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr, bool g77, /* Generate code to deallocate an array, if it is allocated. */ tree -gfc_trans_dealloc_allocated (tree descriptor, bool coarray) +gfc_trans_dealloc_allocated (tree descriptor, bool coarray, gfc_expr *expr) { tree tmp; tree var; @@ -7259,7 +7259,7 @@ gfc_trans_dealloc_allocated (tree descriptor, bool coarray) are already deallocated are ignored. */ tmp = gfc_deallocate_with_status (coarray ? descriptor : var, NULL_TREE, NULL_TREE, NULL_TREE, NULL_TREE, true, - NULL, coarray); + expr, coarray); gfc_add_expr_to_block (&block, tmp); /* Zero the data pointer. */ @@ -7548,7 +7548,7 @@ structure_alloc_comps (gfc_symbol * der_type, tree decl, { comp = fold_build3_loc (input_location, COMPONENT_REF, ctype, decl, cdecl, NULL_TREE); - tmp = gfc_trans_dealloc_allocated (comp, c->attr.codimension); + tmp = gfc_trans_dealloc_allocated (comp, c->attr.codimension, NULL); gfc_add_expr_to_block (&tmpblock, tmp); } else if (c->attr.allocatable) @@ -7580,7 +7580,7 @@ structure_alloc_comps (gfc_symbol * der_type, tree decl, if (GFC_DESCRIPTOR_TYPE_P (TREE_TYPE (comp))) tmp = gfc_trans_dealloc_allocated (comp, - CLASS_DATA (c)->attr.codimension); + CLASS_DATA (c)->attr.codimension, NULL); else { tmp = gfc_deallocate_scalar_with_status (comp, NULL_TREE, true, NULL, @@ -8392,7 +8392,7 @@ gfc_trans_deferred_array (gfc_symbol * sym, gfc_wrapped_block * block) && !sym->attr.save && !sym->attr.result) { tmp = gfc_trans_dealloc_allocated (sym->backend_decl, - sym->attr.codimension); + sym->attr.codimension, NULL); gfc_add_expr_to_block (&cleanup, tmp); } diff --git a/gcc/fortran/trans-array.h b/gcc/fortran/trans-array.h index 6f44d79..a7144e5 100644 --- a/gcc/fortran/trans-array.h +++ b/gcc/fortran/trans-array.h @@ -42,7 +42,7 @@ void gfc_trans_dummy_array_bias (gfc_symbol *, tree, gfc_wrapped_block *); /* Generate entry and exit code for g77 calling convention arrays. */ void gfc_trans_g77_array (gfc_symbol *, gfc_wrapped_block *); /* Generate code to deallocate an array, if it is allocated. */ -tree gfc_trans_dealloc_allocated (tree, bool); +tree gfc_trans_dealloc_allocated (tree, bool, gfc_expr *); tree gfc_duplicate_allocatable (tree dest, tree src, tree type, int rank); diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c index 07b0fa6..85d6cd1 100644 --- a/gcc/fortran/trans-expr.c +++ b/gcc/fortran/trans-expr.c @@ -4274,10 +4274,8 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym, if (e->ts.type == BT_CLASS) ptr = gfc_class_data_get (ptr); - tmp = gfc_deallocate_with_status (ptr, NULL_TREE, - NULL_TREE, NULL_TREE, - NULL_TREE, true, NULL, - false); + tmp = gfc_deallocate_scalar_with_status (ptr, NULL_TREE, + true, e, e->ts); gfc_add_expr_to_block (&block, tmp); tmp = fold_build2_loc (input_location, MODIFY_EXPR, void_type_node, ptr, @@ -4511,7 +4509,7 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym, { tmp = build_fold_indirect_ref_loc (input_location, parmse.expr); - tmp = gfc_trans_dealloc_allocated (tmp, false); + tmp = gfc_trans_dealloc_allocated (tmp, false, e); if (fsym->attr.optional && e->expr_type == EXPR_VARIABLE && e->symtree->n.sym->attr.optional) diff --git a/gcc/fortran/trans-openmp.c b/gcc/fortran/trans-openmp.c index 882927e..2765561 100644 --- a/gcc/fortran/trans-openmp.c +++ b/gcc/fortran/trans-openmp.c @@ -325,7 +325,7 @@ gfc_omp_clause_dtor (tree clause ATTRIBUTE_UNUSED, tree decl) /* Allocatable arrays in FIRSTPRIVATE/LASTPRIVATE etc. clauses need to be deallocated if they were allocated. */ - return gfc_trans_dealloc_allocated (decl, false); + return gfc_trans_dealloc_allocated (decl, false, NULL); } @@ -707,7 +707,8 @@ gfc_trans_omp_array_reduction (tree c, gfc_symbol *sym, locus where) gfc_start_block (&block); gfc_add_expr_to_block (&block, gfc_trans_assignment (e3, e4, false, true)); - gfc_add_expr_to_block (&block, gfc_trans_dealloc_allocated (decl, false)); + gfc_add_expr_to_block (&block, gfc_trans_dealloc_allocated (decl, false, + NULL)); stmt = gfc_finish_block (&block); } else diff --git a/gcc/fortran/trans-stmt.c b/gcc/fortran/trans-stmt.c index 7812934..1ef423b 100644 --- a/gcc/fortran/trans-stmt.c +++ b/gcc/fortran/trans-stmt.c @@ -5398,7 +5398,8 @@ gfc_trans_deallocate (gfc_code *code) if (expr->rank || gfc_is_coarray (expr)) { - if (expr->ts.type == BT_DERIVED && expr->ts.u.derived->attr.alloc_comp) + if (expr->ts.type == BT_DERIVED && expr->ts.u.derived->attr.alloc_comp + && !gfc_is_finalizable (expr->ts.u.derived, NULL)) { gfc_ref *ref; gfc_ref *last = NULL; diff --git a/gcc/fortran/trans.c b/gcc/fortran/trans.c index 8211573..cc3d0d2 100644 --- a/gcc/fortran/trans.c +++ b/gcc/fortran/trans.c @@ -930,6 +930,7 @@ gfc_deallocate_with_status (tree pointer, tree status, tree errmsg, /* When POINTER is not NULL, we free it. */ gfc_start_block (&non_null); + gfc_add_finalizer_call (&non_null, expr); if (!coarray || gfc_option.coarray != GFC_FCOARRAY_LIB) { tmp = build_call_expr_loc (input_location, @@ -1141,6 +1142,115 @@ gfc_build_final_call (gfc_typespec ts, gfc_expr *final_wrapper, gfc_expr *var, } +/* Add a call to the finalizer, using the passed *expr. Returns + true when a finalizer call has been inserted. */ + +bool +gfc_add_finalizer_call (stmtblock_t *block, gfc_expr *expr2) +{ + tree tmp; + gfc_ref *ref; + gfc_expr *expr; + gfc_expr *final_expr = NULL; + gfc_expr *elem_size = NULL; + bool has_finalizer = false; + + if (!expr2) + return false; + + if (expr2->ts.type == BT_DERIVED) + { + gfc_is_finalizable (expr2->ts.u.derived, &final_expr); + if (!final_expr) + return false; + } + + /* If we have a class array, we need go back to the class + container. */ + expr = gfc_copy_expr (expr2); + + if (expr->ref && expr->ref->next && !expr->ref->next->next + && expr->ref->next->type == REF_ARRAY + && expr->ref->next->u.ar.type == AR_FULL + && expr->ref->type == REF_COMPONENT + && strcmp (expr->ref->u.c.component->name, "_data") == 0) + { + gfc_free_ref_list (expr->ref); + expr->ref = NULL; + } + else + for (ref = expr->ref; ref; ref = ref->next) + if (ref->next && ref->next->next && !ref->next->next->next + && ref->next->next->type == REF_ARRAY + && ref->next->next->u.ar.type == AR_FULL + && ref->next->type == REF_COMPONENT + && strcmp (ref->next->u.c.component->name, "_data") == 0) + { + gfc_free_ref_list (ref->next); + ref->next = NULL; + } + + if (expr->ts.type == BT_CLASS) + { + has_finalizer = gfc_is_finalizable (expr->ts.u.derived, NULL); + + final_expr = gfc_copy_expr (expr); + gfc_add_vptr_component (final_expr); + gfc_add_component_ref (final_expr, "_final"); + + elem_size = gfc_copy_expr (expr); + gfc_add_vptr_component (elem_size); + gfc_add_component_ref (elem_size, "_size"); + } + + gcc_assert (final_expr->expr_type == EXPR_VARIABLE); + + tmp = gfc_build_final_call (expr->ts, final_expr, expr, + false, elem_size); + + if (expr->ts.type == BT_CLASS && !has_finalizer) + { + tree cond; + gfc_se se; + + gfc_init_se (&se, NULL); + se.want_pointer = 1; + gfc_conv_expr (&se, final_expr); + cond = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, + se.expr, build_int_cst (TREE_TYPE (se.expr), 0)); + + /* For CLASS(*) not only sym->_vtab->_final can be NULL + but already sym->_vtab itself. */ + if (UNLIMITED_POLY (expr)) + { + tree cond2; + gfc_expr *vptr_expr; + + vptr_expr = gfc_copy_expr (expr); + gfc_add_vptr_component (vptr_expr); + + gfc_init_se (&se, NULL); + se.want_pointer = 1; + gfc_conv_expr (&se, vptr_expr); + gfc_free_expr (vptr_expr); + + cond2 = fold_build2_loc (input_location, NE_EXPR, boolean_type_node, + se.expr, + build_int_cst (TREE_TYPE (se.expr), 0)); + cond = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR, + boolean_type_node, cond2, cond); + } + + tmp = fold_build3_loc (input_location, COND_EXPR, void_type_node, + cond, tmp, build_empty_stmt (input_location)); + } + + gfc_add_expr_to_block (block, tmp); + + return true; +} + + /* Generate code for deallocation of allocatable scalars (variables or components). Before the object itself is freed, any allocatable subcomponents are being deallocated. */ @@ -1151,6 +1261,7 @@ gfc_deallocate_scalar_with_status (tree pointer, tree status, bool can_fail, { stmtblock_t null, non_null; tree cond, tmp, error; + bool finalizable; cond = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node, pointer, build_int_cst (TREE_TYPE (pointer), 0)); @@ -1195,20 +1306,13 @@ gfc_deallocate_scalar_with_status (tree pointer, tree status, bool can_fail, gfc_start_block (&non_null); /* Free allocatable components. */ - if (ts.type == BT_DERIVED && ts.u.derived->attr.alloc_comp) + finalizable = gfc_add_finalizer_call (&non_null, expr); + if (!finalizable && ts.type == BT_DERIVED && ts.u.derived->attr.alloc_comp) { tmp = build_fold_indirect_ref_loc (input_location, pointer); tmp = gfc_deallocate_alloc_comp (ts.u.derived, tmp, 0); gfc_add_expr_to_block (&non_null, tmp); } - else if (ts.type == BT_CLASS - && ts.u.derived->components->ts.u.derived->attr.alloc_comp) - { - tmp = build_fold_indirect_ref_loc (input_location, pointer); - tmp = gfc_deallocate_alloc_comp (ts.u.derived->components->ts.u.derived, - tmp, 0); - gfc_add_expr_to_block (&non_null, tmp); - } tmp = build_call_expr_loc (input_location, builtin_decl_explicit (BUILT_IN_FREE), 1, diff --git a/gcc/fortran/trans.h b/gcc/fortran/trans.h index 0c0fe5d..957238e 100644 --- a/gcc/fortran/trans.h +++ b/gcc/fortran/trans.h @@ -354,6 +354,8 @@ tree gfc_get_class_array_ref (tree, tree); tree gfc_copy_class_to_class (tree, tree, tree); tree gfc_build_final_call (gfc_typespec, gfc_expr *, gfc_expr *, bool, gfc_expr *); +bool gfc_add_finalizer_call (stmtblock_t *, gfc_expr *); + void gfc_conv_derived_to_class (gfc_se *, gfc_expr *, gfc_typespec, tree, bool, bool); void gfc_conv_class_to_class (gfc_se *, gfc_expr *, gfc_typespec, bool, bool, --- /dev/null 2013-05-27 09:23:19.299118255 +0200 +++ gcc/gcc/testsuite/gfortran.dg/finalize_12.f90 2013-05-27 19:56:52.479822874 +0200 @@ -0,0 +1,103 @@ +module m + implicit none + type t + integer :: i + contains + final :: fini, fini2 + end type t + integer :: global_count1, global_count2 +contains + subroutine fini(x) + type(t) :: x +! print *, 'fini:',x%i + if (global_count1 == -1) call abort () + if (x%i /= 42) call abort() + x%i = 33 + global_count1 = global_count1 + 1 + end subroutine fini + subroutine fini2(x) + type(t) :: x(:) + print *, 'fini2', x%i + if (global_count1 == -1) call abort () + if (size(x) /= 5) call abort() + if (any (x%i /= [1,2,3,4,5]) .and. any (x%i /= [6,7,8,9,10])) call abort() + x%i = 33 + global_count2 = global_count2 + 10 + end subroutine fini2 +end module m + +program pp + use m + implicit none + type(t), allocatable :: ya + class(t), allocatable :: yc + type(t), allocatable :: yaa(:) + class(t), allocatable :: yca(:) + + global_count1 = -1 + global_count2 = -1 + allocate (ya, yc, yaa(5), yca(5)) + global_count1 = 0 + global_count2 = 0 + ya%i = 42 + yc%i = 42 + yaa%i = [1,2,3,4,5] + yca%i = [1,2,3,4,5] + + call foo(ya, yc, yaa, yca) + if (global_count1 /= 2) call abort () + if (global_count2 /= 20) call abort () + + block + type(t), allocatable :: za + class(t), allocatable :: zc + type(t), allocatable :: zaa(:) + class(t), allocatable :: zca(:) + + allocate (za, zc, zaa(5), zca(5)) + global_count1 = 0 + global_count2 = 0 + za%i = 42 + zc%i = 42 + zaa%i = [1,2,3,4,5] + zca%i = [1,2,3,4,5] + + call foo(za, zc, zaa, zca) + if (global_count1 /= 2) call abort () + if (global_count2 /= 20) call abort () + + allocate (za, zc, zaa(5), zca(5)) + global_count1 = 0 + global_count2 = 0 + za%i = 42 + zc%i = 42 + zaa%i = [1,2,3,4,5] + zca%i = [6,7,8,9,10] + + print *, 'BLOCK DONE' + end block + + if (global_count1 /= 2) call abort () +print *, 'XXXX', global_count2 ! <<<< MISSED FINALIZATION of "zaa"! +! if (global_count2 /= 20) call abort () + + allocate (ya, yc, yaa(5), yca(5)) +! global_count1 = -1 ! FIXME: Wrong deallocate at end of scope +! global_count2 = -1 ! FIXME: Wrong deallocate at end of scope + ya%i = 42 ! REMOVE when fixed + yc%i = 42 ! REMOVE when fixed + yaa%i = [1,2,3,4,5] ! REMOVE when fixed + yca%i = [1,2,3,4,5] ! REMOVE when fixed + +contains + subroutine foo(xa, xc, xaa, xca) + type(t), allocatable, intent(out) :: xa + class(t), allocatable, intent(out) :: xc + type(t), allocatable, intent(out) :: xaa(:) + class(t), allocatable, intent(out) :: xca(:) + if (allocated (xa)) call abort () + if (allocated (xc)) call abort () + if (allocated (xaa)) call abort () + if (allocated (xca)) call abort () + end subroutine foo +end program