[Patch, fortran] PR49213 - [OOP] gfortran rejects structure constructor expression
Hi All, I was looking through Neil Carlson's collection of gfortran bugs and was shocked to find this rather fundamental PR. At 12 years old, it is certainly a "golden oldie"! The patch is rather straightforward and seems to do the job of admitting derived, intrinsic and character expressions to allocatable class components in structure constructors. I have included the adjustment to 'gfc_is_ptr_fcn' and eliminating the extra blank line, introduced by my last patch. I played safe and went exclusively for class functions with attr.class_pointer set on the grounds that these have had all the accoutrements checked and built (ie. class_ok). I am still not sure if this is necessary or not. OK for trunk? Paul Fortran: Enable class expressions in structure constructors [PR49213] 2023-06-24 Paul Thomas gcc/fortran PR fortran/49213 * expr.cc (gfc_is_ptr_fcn): Guard pointer attribute to exclude class expressions. * resolve.cc (resolve_assoc_var): Call gfc_is_ptr_fcn to allow associate names with pointer function targets to be used in variable definition context. * trans-decl.cc (get_symbol_decl): Remove extraneous line. * trans-expr.cc (alloc_scalar_allocatable_subcomponent): Obtain size of intrinsic and character expressions. (gfc_trans_subcomponent_assign): Expand assignment to class components to include intrinsic and character expressions. gcc/testsuite/ PR fortran/49213 * gfortran.dg/pr49213.f90 : New test diff --git a/gcc/fortran/expr.cc b/gcc/fortran/expr.cc index c960dfeabd9..92061d69781 100644 --- a/gcc/fortran/expr.cc +++ b/gcc/fortran/expr.cc @@ -816,7 +816,7 @@ bool gfc_is_ptr_fcn (gfc_expr *e) { return e != NULL && e->expr_type == EXPR_FUNCTION - && (gfc_expr_attr (e).pointer + && ((e->ts.type != BT_CLASS && gfc_expr_attr (e).pointer) || (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.class_pointer)); } diff --git a/gcc/fortran/resolve.cc b/gcc/fortran/resolve.cc index 82e6ac53aa1..217d69d4e0b 100644 --- a/gcc/fortran/resolve.cc +++ b/gcc/fortran/resolve.cc @@ -1350,6 +1350,9 @@ resolve_structure_cons (gfc_expr *expr, int init) && CLASS_DATA (comp)->as) rank = CLASS_DATA (comp)->as->rank; + if (comp->ts.type == BT_CLASS && cons->expr->ts.type == BT_DERIVED) + gfc_find_derived_vtab (cons->expr->ts.u.derived); + if (cons->expr->expr_type != EXPR_NULL && rank != cons->expr->rank && (comp->attr.allocatable || cons->expr->rank)) { @@ -1381,7 +1384,7 @@ resolve_structure_cons (gfc_expr *expr, int init) gfc_basic_typename (comp->ts.type)); t = false; } - else + else if (!UNLIMITED_POLY (comp)) { bool t2 = gfc_convert_type (cons->expr, &comp->ts, 1); if (t) diff --git a/gcc/fortran/trans-decl.cc b/gcc/fortran/trans-decl.cc index 18589e17843..b0fd25e92a3 100644 --- a/gcc/fortran/trans-decl.cc +++ b/gcc/fortran/trans-decl.cc @@ -1915,7 +1915,6 @@ gfc_get_symbol_decl (gfc_symbol * sym) gcc_assert (!sym->value || sym->value->expr_type == EXPR_NULL); } - gfc_finish_var_decl (decl, sym); if (sym->ts.type == BT_CHARACTER) diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc index 3c209bcde97..5a1ff0c1d21 100644 --- a/gcc/fortran/trans-expr.cc +++ b/gcc/fortran/trans-expr.cc @@ -8781,6 +8781,7 @@ alloc_scalar_allocatable_subcomponent (stmtblock_t *block, tree comp, tree size; tree size_in_bytes; tree lhs_cl_size = NULL_TREE; + gfc_se se; if (!comp) return; @@ -8815,16 +8816,26 @@ alloc_scalar_allocatable_subcomponent (stmtblock_t *block, tree comp, } else if (cm->ts.type == BT_CLASS) { - gcc_assert (expr2->ts.type == BT_CLASS || expr2->ts.type == BT_DERIVED); - if (expr2->ts.type == BT_DERIVED) + if (expr2->ts.type != BT_CLASS) { - tmp = gfc_get_symbol_decl (expr2->ts.u.derived); - size = TYPE_SIZE_UNIT (tmp); + if (expr2->ts.type == BT_CHARACTER) + { + gfc_init_se (&se, NULL); + gfc_conv_expr (&se, expr2); + size = fold_convert (size_type_node, se.string_length); + } + else + { + if (expr2->ts.type == BT_DERIVED) + tmp = gfc_get_symbol_decl (expr2->ts.u.derived); + else + tmp = gfc_typenode_for_spec (&expr2->ts); + size = TYPE_SIZE_UNIT (tmp); + } } else { gfc_expr *e2vtab; - gfc_se se; e2vtab = gfc_find_and_cut_at_last_class_ref (expr2); gfc_add_vptr_component (e2vtab); gfc_add_size_component (e2vtab); @@ -8975,6 +8986,7 @@ gfc_trans_subcomponent_assign (tree dest, gfc_component * cm, { gfc_init_se (&se, NULL); gfc_conv_expr (&se, expr); + tree size; /* Take care about non-array allocatable components here. The alloc_* routine below is motivated by the alloc_scalar_allocatable_for_ @@ -8990,7 +9002,7 @@ gfc_trans_subcomponent_assign (tree dest, gfc_component * cm, && expr->symtree->n.sym->attr.dummy) se.expr = build_fold_indirect_ref_loc (input_location, se.expr); - if (cm->ts.type =
PR82943 - Suggested patch to fix
Hello, I am new to the GFortran community. Over the past two weeks I created a patch that should fix PR82943 for GFortran. I have attached it to this email. The patch allows the code below to compile successfully. I am working on creating test cases next, but I am new to the process so it may take me some time. After I make test cases, do I email them to you as well? Do I need to make a pull-request on github in order to get the patch reviewed? Thank you, Alexander Westbrooks module testmod public :: foo type, public :: tough_lvl_0(a, b) integer, kind :: a = 1 integer, len :: b contains procedure :: foo end type type, public, EXTENDS(tough_lvl_0) :: tough_lvl_1 (c) integer, len :: c contains procedure :: bar end type type, public, EXTENDS(tough_lvl_1) :: tough_lvl_2 (d) integer, len :: d contains procedure :: foobar end type contains subroutine foo(this) class(tough_lvl_0(1,*)), intent(inout) :: this end subroutine subroutine bar(this) class(tough_lvl_1(1,*,*)), intent(inout) :: this end subroutine subroutine foobar(this) class(tough_lvl_2(1,*,*,*)), intent(inout) :: this end subroutine end module PROGRAM testprogram USE testmod TYPE(tough_lvl_0(1,5)) :: test_pdt_0 TYPE(tough_lvl_1(1,5,6)) :: test_pdt_1 TYPE(tough_lvl_2(1,5,6,7)) :: test_pdt_2 CALL test_pdt_0%foo() CALL test_pdt_1%foo() CALL test_pdt_1%bar() CALL test_pdt_2%foo() CALL test_pdt_2%bar() CALL test_pdt_2%foobar() END PROGRAM testprogram 0001-bug-patch-PR82943.patch Description: Binary data
[PATCH, part2, committed] Fortran: ABI for scalar CHARACTER(LEN=1),VALUE dummy argument [PR110360]
Dear all, the first part of the patch came with a testcase that also exercised code for constant string arguments, which was not touched by that patch but seems to have caused runtime failures on big-endian platforms (e.g. Power-* BE) for all optimization levels, and on x86 / -m32 at -O1 and higher (not at -O0). I did not see any issues on x86 / -m64 and any optimization level, but could reproduce a problem with x86 / -m32 at -O1, which appears to be related how arguments that are to be passed by value are handled when there is a mismatch between the function prototype and the passed argument. The solution is to truncate too long constant string arguments, fixed by the attached patch, pushed as: https://gcc.gnu.org/g:3f97d10aa1ff5984d6fd657f246d3f251b254ff1 and see attached. * * * I found gcc-testresults quite helpful in checking whether my patch caused trouble on architectures different from the one I'm working on. The value (pun intended) would have been even greater if output of runtime failures would also be made available. Many (Fortran) tests provide either a stop code, or some hopefully helpful diagnostic output on stdout intended for locating errors on platforms where one has no direct access to, or is less familiar with. Far better than a plain FAIL: gfortran.dg/value_9.f90 -O1 execution test * * * Thanks, Harald From 3f97d10aa1ff5984d6fd657f246d3f251b254ff1 Mon Sep 17 00:00:00 2001 From: Harald Anlauf Date: Sat, 24 Jun 2023 20:36:53 +0200 Subject: [PATCH] Fortran: ABI for scalar CHARACTER(LEN=1),VALUE dummy argument [PR110360] gcc/fortran/ChangeLog: PR fortran/110360 * trans-expr.cc (gfc_conv_procedure_call): Truncate constant string argument of length > 1 passed to scalar CHARACTER(1),VALUE dummy. --- gcc/fortran/trans-expr.cc | 21 + 1 file changed, 13 insertions(+), 8 deletions(-) diff --git a/gcc/fortran/trans-expr.cc b/gcc/fortran/trans-expr.cc index c92fccd0be2..63e3cf9681e 100644 --- a/gcc/fortran/trans-expr.cc +++ b/gcc/fortran/trans-expr.cc @@ -6395,20 +6395,25 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym, /* ABI: actual arguments to CHARACTER(len=1),VALUE dummy arguments are actually passed by value. - The BIND(C) case is handled elsewhere. - TODO: truncate constant strings to length 1. */ + Constant strings are truncated to length 1. + The BIND(C) case is handled elsewhere. */ if (fsym->ts.type == BT_CHARACTER && !fsym->ts.is_c_interop && fsym->ts.u.cl->length->expr_type == EXPR_CONSTANT && fsym->ts.u.cl->length->ts.type == BT_INTEGER && (mpz_cmp_ui - (fsym->ts.u.cl->length->value.integer, 1) == 0) - && e->expr_type != EXPR_CONSTANT) + (fsym->ts.u.cl->length->value.integer, 1) == 0)) { - parmse.expr = gfc_string_to_single_character - (build_int_cst (gfc_charlen_type_node, 1), - parmse.expr, - e->ts.kind); + if (e->expr_type != EXPR_CONSTANT) + parmse.expr = gfc_string_to_single_character + (build_int_cst (gfc_charlen_type_node, 1), + parmse.expr, + e->ts.kind); + else if (e->value.character.length > 1) + { + e->value.character.length = 1; + gfc_conv_expr (&parmse, e); + } } if (fsym->attr.optional -- 2.35.3
Re: [Patch, fortran] PR49213 - [OOP] gfortran rejects structure constructor expression
Hi Paul! On 6/24/23 15:18, Paul Richard Thomas via Gcc-patches wrote: I have included the adjustment to 'gfc_is_ptr_fcn' and eliminating the extra blank line, introduced by my last patch. I played safe and went exclusively for class functions with attr.class_pointer set on the grounds that these have had all the accoutrements checked and built (ie. class_ok). I am still not sure if this is necessary or not. maybe it is my fault, but I find the version in the patch confusing: @@ -816,7 +816,7 @@ bool gfc_is_ptr_fcn (gfc_expr *e) { return e != NULL && e->expr_type == EXPR_FUNCTION - && (gfc_expr_attr (e).pointer + && ((e->ts.type != BT_CLASS && gfc_expr_attr (e).pointer) || (e->ts.type == BT_CLASS && CLASS_DATA (e)->attr.class_pointer)); } The caller 'gfc_is_ptr_fcn' has e->expr_type == EXPR_FUNCTION, so gfc_expr_attr (e) boils down to: if (e->value.function.esym && e->value.function.esym->result) { gfc_symbol *sym = e->value.function.esym->result; attr = sym->attr; if (sym->ts.type == BT_CLASS && sym->attr.class_ok) { attr.dimension = CLASS_DATA (sym)->attr.dimension; attr.pointer = CLASS_DATA (sym)->attr.class_pointer; attr.allocatable = CLASS_DATA (sym)->attr.allocatable; } } ... else if (e->symtree) attr = gfc_variable_attr (e, NULL); So I thought this should already do what you want if you do gfc_is_ptr_fcn (gfc_expr *e) { return e != NULL && e->expr_type == EXPR_FUNCTION && gfc_expr_attr (e).pointer; } or what am I missing? The additional checks in gfc_expr_attr are there to avoid ICEs in case CLASS_DATA (sym) has issues, and we all know Gerhard who showed that he is an expert in exploiting this. To sum up, I'd prefer to use the safer form if it works. If it doesn't, I would expect a latent issue. The rest of the code looked good to me, but I was suspicious about the handling of CHARACTER. Nasty as I am, I modified the testcase to use character(kind=4) instead of kind=1 (see attached). This either fails here (stop 10), or if I activate the marked line !cont = tContainer('hello!') ! ### ICE! ### I get an ICE. Can you have another look? Thanks, Harald OK for trunk? Paul Fortran: Enable class expressions in structure constructors [PR49213] 2023-06-24 Paul Thomas gcc/fortran PR fortran/49213 * expr.cc (gfc_is_ptr_fcn): Guard pointer attribute to exclude class expressions. * resolve.cc (resolve_assoc_var): Call gfc_is_ptr_fcn to allow associate names with pointer function targets to be used in variable definition context. * trans-decl.cc (get_symbol_decl): Remove extraneous line. * trans-expr.cc (alloc_scalar_allocatable_subcomponent): Obtain size of intrinsic and character expressions. (gfc_trans_subcomponent_assign): Expand assignment to class components to include intrinsic and character expressions. gcc/testsuite/ PR fortran/49213 * gfortran.dg/pr49213.f90 : New test ! { dg-do run } ! ! Contributed by Neil Carlson ! program main ! character(2) :: c character(2,kind=4) :: c type :: S integer :: n end type type(S) :: Sobj type, extends(S) :: S2 integer :: m end type type(S2) :: S2obj type :: T class(S), allocatable :: x end type type(T) :: Tobj Sobj = S(1) Tobj = T(Sobj) S2obj = S2(1,2) Tobj = T(S2obj)! Failed here select type (x => Tobj%x) type is (S2) if ((x%n .ne. 1) .or. (x%m .ne. 2)) stop 1 class default stop 2 end select c = 4_" " call pass_it (T(Sobj)) if (c .ne. 4_"S ") stop 3 call pass_it (T(S2obj))! and here if (c .ne. 4_"S2") stop 4 call bar contains subroutine pass_it (foo) type(T), intent(in) :: foo select type (x => foo%x) type is (S) c = 4_"S " if (x%n .ne. 1) stop 5 type is (S2) c = 4_"S2" if ((x%n .ne. 1) .or. (x%m .ne. 2)) stop 6 class default stop 7 end select end subroutine subroutine bar ! Test from comment #29 of the PR - due to Janus Weil type tContainer class(*), allocatable :: x end type integer, parameter :: i = 0 character(7,kind=4) :: chr = 4_"goodbye" type(tContainer) :: cont cont%x = i ! linker error: undefined reference to `__copy_INTEGER_4_.3804' cont = tContainer(i+42) ! Failed here select type (z => cont%x) type is (integer) if (z .ne. 42) stop 8 class default stop 9 end select !cont = tContainer('hello!') ! ### ICE! ### cont = tContainer(4_'hello!') select type (z => cont%x) type is (character(*,kind=4)) if (z .ne. 4_'hello!') stop 10 class default stop 11 end select cont = tContainer(chr) select type (z => cont%x) type is (character(*,kind=4)) if (z .ne. 4_'goodbye') stop 12 class default